shakespeare-2.1.0.1: A toolkit for making compile-time interpolated templates
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Shakespeare.Base

Description

General parsers, functions and datatypes for all Shakespeare languages.

Synopsis

Documentation

data Deref Source #

Constructors

DerefModulesIdent [String] Ident 
DerefIdent Ident 
DerefIntegral Integer 
DerefRational Rational 
DerefString String 
DerefBranch Deref Deref 
DerefList [Deref] 
DerefTuple [Deref] 
DerefGetField Deref String

Record field access via OverloadedRecordDot. derefToExp only supports this feature on compilers which support OverloadedRecordDot.

Since: 2.1.0

Instances

Instances details
Data Deref Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Deref -> c Deref #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Deref #

toConstr :: Deref -> Constr #

dataTypeOf :: Deref -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Deref) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Deref) #

gmapT :: (forall b. Data b => b -> b) -> Deref -> Deref #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r #

gmapQ :: (forall d. Data d => d -> u) -> Deref -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Deref -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Deref -> m Deref #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Deref -> m Deref #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Deref -> m Deref #

Read Deref Source # 
Instance details

Defined in Text.Shakespeare.Base

Show Deref Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

showsPrec :: Int -> Deref -> ShowS #

show :: Deref -> String #

showList :: [Deref] -> ShowS #

Eq Deref Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

(==) :: Deref -> Deref -> Bool #

(/=) :: Deref -> Deref -> Bool #

Ord Deref Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

compare :: Deref -> Deref -> Ordering #

(<) :: Deref -> Deref -> Bool #

(<=) :: Deref -> Deref -> Bool #

(>) :: Deref -> Deref -> Bool #

(>=) :: Deref -> Deref -> Bool #

max :: Deref -> Deref -> Deref #

min :: Deref -> Deref -> Deref #

Lift Deref Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

lift :: Quote m => Deref -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Deref -> Code m Deref #

newtype Ident Source #

Constructors

Ident String 

Instances

Instances details
Data Ident Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ident -> c Ident #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ident #

toConstr :: Ident -> Constr #

dataTypeOf :: Ident -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ident) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident) #

gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ident -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

Read Ident Source # 
Instance details

Defined in Text.Shakespeare.Base

Show Ident Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Eq Ident Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Ord Ident Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

(>=) :: Ident -> Ident -> Bool #

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Lift Ident Source # 
Instance details

Defined in Text.Shakespeare.Base

Methods

lift :: Quote m => Ident -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Ident -> Code m Ident #

type Scope = [(Ident, Exp)] Source #

parseDeref :: UserParser a Deref Source #

parseHash :: UserParser a (Either String Deref) Source #

parseVar :: Char -> UserParser a (Either String Deref) Source #

parseAt :: UserParser a (Either String (Deref, Bool)) Source #

parseUrl :: Char -> Char -> UserParser a (Either String (Deref, Bool)) Source #

parseCaret :: UserParser a (Either String Deref) Source #

parseUnder :: UserParser a (Either String Deref) Source #

parseInt :: Char -> UserParser a (Either String Deref) Source #

readUtf8FileString :: FilePath -> IO String Source #

Read file's content as String, converting newlines

Since: 2.0.19

readFileQ :: FilePath -> Q String Source #

Embed file's content, converting newlines

Since: 2.0.19

readFileRecompileQ :: FilePath -> Q String Source #

Embed file's content, converting newlines and track file via ghc dependencies, recompiling on changes

Since: 2.0.19