shakespeare-2.0.11.2: A toolkit for making compile-time interpolated templates

Safe HaskellNone
LanguageHaskell98

Text.Shakespeare

Contents

Description

NOTE: This module should be considered internal, and will be hidden in future releases.

Synopsis

Documentation

data ShakespeareSettings Source #

Constructors

ShakespeareSettings 

Fields

data PreConvert Source #

Coffeescript, TypeScript, and other languages compiles down to Javascript. Previously we waited until the very end, at the rendering stage to perform this compilation. Lets call is a post-conversion This had the advantage that all Haskell values were inserted first: for example a value could be inserted that Coffeescript would compile into Javascript. While that is perhaps a safer approach, the advantage is not used in practice: it was that way mainly for ease of implementation. The down-side is the template must be compiled down to Javascript during every request. If instead we do a pre-conversion to compile down to Javascript, we only need to perform the compilation once.

The problem then is the insertion of Haskell values: we need a hole for them. This can be done with variables known to the language. During the pre-conversion we first modify all Haskell insertions So #{a} is change to shakespeare_var_a Then we can place the Haskell values in a function wrapper that exposes those variables: (function(shakespeare_var_a){ ... shakespeare_var_a ...}) TypeScript can compile that, and then we tack an application of the Haskell values onto the result: (#{a})

preEscapeIgnoreBalanced is used to not insert backtacks for variable already inside strings or backticks. coffeescript will happily ignore the interpolations, and backticks would not be treated as escaping in that context. preEscapeIgnoreLine was added to ignore comments (which in Coffeescript begin with a #)

Instances

low-level

shakespeareUsedIdentifiers :: ShakespeareSettings -> String -> [(Deref, VarType)] Source #

Determine which identifiers are used by the given template, useful for creating systems like yesod devel.

type RenderUrl url = url -> QueryParameters -> Text Source #

data VarType Source #

Constructors

VTPlain 
VTUrl 
VTUrlParam 
VTMixin 

Instances

Bounded VarType Source # 
Enum VarType Source # 
Eq VarType Source # 

Methods

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

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

Data VarType Source # 

Methods

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

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

toConstr :: VarType -> Constr #

dataTypeOf :: VarType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord VarType Source # 
Show VarType Source # 
Generic VarType Source # 

Associated Types

type Rep VarType :: * -> * #

Methods

from :: VarType -> Rep VarType x #

to :: Rep VarType x -> VarType #

type Rep VarType Source # 
type Rep VarType = D1 (MetaData "VarType" "Text.Shakespeare" "shakespeare-2.0.11.2-5TFV2jmzEJP5w06D4Oup54" False) ((:+:) ((:+:) (C1 (MetaCons "VTPlain" PrefixI False) U1) (C1 (MetaCons "VTUrl" PrefixI False) U1)) ((:+:) (C1 (MetaCons "VTUrlParam" PrefixI False) U1) (C1 (MetaCons "VTMixin" PrefixI False) U1)))

data Deref Source #

Instances

Eq Deref Source # 

Methods

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

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

Data Deref Source # 

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 :: (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 #

Ord Deref Source # 

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 #

Read Deref Source # 
Show Deref Source # 

Methods

showsPrec :: Int -> Deref -> ShowS #

show :: Deref -> String #

showList :: [Deref] -> ShowS #

Lift Deref Source # 

Methods

lift :: Deref -> Q Exp #

type Parser = Parsec String [String] Source #

A parser with a user state of [String]

preFilter Source #

Arguments

:: Maybe FilePath

for error reporting

-> ShakespeareSettings 
-> String 
-> IO String 

Internal

shakespeareRuntime :: ShakespeareSettings -> FilePath -> [(Deref, VarExp url)] -> Shakespeare url Source #