{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
module Text.RE.Types.Options where
import Data.Hashable
import qualified Data.HashMap.Strict as HM
import Data.String
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
data Options_ r c e =
Options
{ optionsMacs :: !(Macros r)
, optionsComp :: !c
, optionsExec :: !e
}
deriving (Show)
class IsOption o r c e |
e -> r, c -> e , e -> c, r -> c, c -> r, r -> e where
makeOptions :: o -> Options_ r c e
newtype MacroID =
MacroID { getMacroID :: String }
deriving (IsString,Ord,Eq,Show)
instance Hashable MacroID where
hashWithSalt i = hashWithSalt i . getMacroID
type Macros r = HM.HashMap MacroID r
emptyMacros :: Macros r
emptyMacros = HM.empty
data SimpleRegexOptions
= MultilineSensitive
| MultilineInsensitive
| BlockSensitive
| BlockInsensitive
deriving (Bounded,Enum,Eq,Ord,Show)
instance Lift SimpleRegexOptions where
lift sro = case sro of
MultilineSensitive -> conE 'MultilineSensitive
MultilineInsensitive -> conE 'MultilineInsensitive
BlockSensitive -> conE 'BlockSensitive
BlockInsensitive -> conE 'BlockInsensitive