tophat-1.0.5.1: Template-to-Haskell preprocessor, and templating language
Safe HaskellNone
LanguageHaskell2010

Tophat

Description

A library providing support for templating

Synopsis

Basic functionality

class Context s a r | r -> s, r -> a Source #

A Context records the situation part-way through a template (in the middle of control structures, perhaps).

Minimal complete definition

prolong

Instances

Instances details
Semigroup s => Context s a (Template a s) Source #

A Template is the basic example of a Context

Instance details

Defined in Tophat

Methods

prolong :: Template a s -> Template a s -> Template a s

(Semigroup t, Context s a r) => Context t a (ProcessContext s t a r) Source # 
Instance details

Defined in Tophat

Methods

prolong :: Template a t -> ProcessContext s t a r -> ProcessContext s t a r

(Semigroup s, Context s a r) => Context s b (WithContext s a b r) Source # 
Instance details

Defined in Tophat

Methods

prolong :: Template b s -> WithContext s a b r -> WithContext s a b r

(Semigroup s, Context s a r) => Context s b (IfContext s a b r) Source # 
Instance details

Defined in Tophat

Methods

prolong :: Template b s -> IfContext s a b r -> IfContext s a b r

(Semigroup s, Context s a r) => Context s b (ForContext f s a b r) Source # 
Instance details

Defined in Tophat

Methods

prolong :: Template b s -> ForContext f s a b r -> ForContext f s a b r

data Template a s Source #

A Template a s wraps a function which takes an argument of type a, and is intended to return some IsString type s.

Instances

Instances details
Profunctor Template Source # 
Instance details

Defined in Tophat

Methods

dimap :: (a -> b) -> (c -> d) -> Template b c -> Template a d #

lmap :: (a -> b) -> Template b c -> Template a c #

rmap :: (b -> c) -> Template a b -> Template a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Template a b -> Template a c #

(.#) :: forall a b c q. Coercible b a => Template b c -> q a b -> Template a c #

Semigroup s => Context s a (Template a s) Source #

A Template is the basic example of a Context

Instance details

Defined in Tophat

Methods

prolong :: Template a s -> Template a s -> Template a s

Semigroup s => Semigroup (Template a s) Source # 
Instance details

Defined in Tophat

Methods

(<>) :: Template a s -> Template a s -> Template a s #

sconcat :: NonEmpty (Template a s) -> Template a s #

stimes :: Integral b => b -> Template a s -> Template a s #

Monoid s => Monoid (Template a s) Source # 
Instance details

Defined in Tophat

Methods

mempty :: Template a s #

mappend :: Template a s -> Template a s -> Template a s #

mconcat :: [Template a s] -> Template a s #

makeTemplate :: Monoid s => (Template a s -> Template a s) -> Template a s Source #

We normally manipulate not Templates, but functions which extend templates; this extracts a Template from such a function by applying it to the empty template.

embed :: Context s a r => (a -> s) -> r -> r Source #

Insert something computed from the template argument

embedConst :: Context s a r => s -> r -> r Source #

Insert something not depending upon the template argument

embedShow :: (Context s a r, IsString s, Show b) => (a -> b) -> r -> r Source #

Insert a string representation (obtained by fromString . Show) derived from the template argument

Control structures

for

data ForContext f s a b r Source #

The ForContext control structure iterates over any Foldable data structure: this is quite powerful, and can subsume many of those control structures which follow.

Instances

Instances details
(Semigroup s, Context s a r) => Context s b (ForContext f s a b r) Source # 
Instance details

Defined in Tophat

Methods

prolong :: Template b s -> ForContext f s a b r -> ForContext f s a b r

forH :: Monoid s => (a -> f b) -> r -> ForContext f s a b r Source #

This enters a ForContext.

endfor :: (Monoid s, Context s a r, Foldable f) => ForContext f s a b r -> r Source #

This exits from a ForContext.

if

data IfContext s a b r Source #

The IfContext control structure is a slightly disguised ForContext (using Maybe).

Instances

Instances details
(Semigroup s, Context s a r) => Context s b (IfContext s a b r) Source # 
Instance details

Defined in Tophat

Methods

prolong :: Template b s -> IfContext s a b r -> IfContext s a b r

ifH :: Monoid s => (a -> Bool) -> r -> IfContext s a a r Source #

This enters an IfContext.

endif :: (Monoid s, Context s a r) => IfContext s a a r -> r Source #

This exits from an IfContext.

process

data ProcessContext s t a r Source #

The ProcessContext control structure postprocesses the template output in a region (unlike a WithContext, which preprocesses the template argument).

Instances

Instances details
(Semigroup t, Context s a r) => Context t a (ProcessContext s t a r) Source # 
Instance details

Defined in Tophat

Methods

prolong :: Template a t -> ProcessContext s t a r -> ProcessContext s t a r

procH :: Monoid t => (t -> s) -> r -> ProcessContext s t a r Source #

This enters a ProcessContext.

endproc :: Context s a r => ProcessContext s t a r -> r Source #

This exits from a ProcessContext.

with

data WithContext s a b r Source #

The WithContext control structure changes the argument to the template temporarily. It is intended to be useful in situations where tree-like data structures are passed as arguments, and there is a section of the template where only one branch is of interest. Again, this is a slightly disguised ForContext (using Identity).

Instances

Instances details
(Semigroup s, Context s a r) => Context s b (WithContext s a b r) Source # 
Instance details

Defined in Tophat

Methods

prolong :: Template b s -> WithContext s a b r -> WithContext s a b r

withH :: Monoid s => (a -> b) -> r -> WithContext s a b r Source #

This enters a WithContext.

endwith :: (Monoid s, Context s a r) => WithContext s a b r -> r Source #

This exits from a WithContext.

Re-exported code

(>>>) :: forall k cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c infixr 1 #

Left-to-right composition