ema-0.2.0.0: Static site generator library with hot reload
Safe HaskellNone
LanguageHaskell2010

Ema

Synopsis

Documentation

data Format Source #

Constructors

Html 
Other 

Instances

Instances details
Eq Format Source # 
Instance details

Defined in Ema.Asset

Methods

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

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

Ord Format Source # 
Instance details

Defined in Ema.Asset

Show Format Source # 
Instance details

Defined in Ema.Asset

Generic Format Source # 
Instance details

Defined in Ema.Asset

Associated Types

type Rep Format :: Type -> Type #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

type Rep Format Source # 
Instance details

Defined in Ema.Asset

type Rep Format = D1 ('MetaData "Format" "Ema.Asset" "ema-0.2.0.0-43Q8o53HdSb5nkEd0OygUk" 'False) (C1 ('MetaCons "Html" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Other" 'PrefixI 'False) (U1 :: Type -> Type))

data Asset a Source #

The type of assets that can be bundled in a static site.

Constructors

AssetStatic FilePath

A file that is copied as-is from the source directory.

Relative paths are assumed relative to the source directory. Absolute paths allow copying static files outside of source directory.

AssetGenerated Format a

A file whose contents are generated at runtime by user code.

Instances

Instances details
Eq a => Eq (Asset a) Source # 
Instance details

Defined in Ema.Asset

Methods

(==) :: Asset a -> Asset a -> Bool #

(/=) :: Asset a -> Asset a -> Bool #

Ord a => Ord (Asset a) Source # 
Instance details

Defined in Ema.Asset

Methods

compare :: Asset a -> Asset a -> Ordering #

(<) :: Asset a -> Asset a -> Bool #

(<=) :: Asset a -> Asset a -> Bool #

(>) :: Asset a -> Asset a -> Bool #

(>=) :: Asset a -> Asset a -> Bool #

max :: Asset a -> Asset a -> Asset a #

min :: Asset a -> Asset a -> Asset a #

Show a => Show (Asset a) Source # 
Instance details

Defined in Ema.Asset

Methods

showsPrec :: Int -> Asset a -> ShowS #

show :: Asset a -> String #

showList :: [Asset a] -> ShowS #

Generic (Asset a) Source # 
Instance details

Defined in Ema.Asset

Associated Types

type Rep (Asset a) :: Type -> Type #

Methods

from :: Asset a -> Rep (Asset a) x #

to :: Rep (Asset a) x -> Asset a #

type Rep (Asset a) Source # 
Instance details

Defined in Ema.Asset

class Ema model route | route -> model where Source #

Enrich a model to work with Ema

Minimal complete definition

encodeRoute, decodeRoute

Methods

encodeRoute :: model -> route -> FilePath Source #

Get the filepath on disk corresponding to this route.

decodeRoute :: model -> FilePath -> Maybe route Source #

Decode a filepath on disk into a route.

allRoutes :: model -> [route] Source #

All routes in the site

The gen command will generate only these routes. On live server, this function is never used.

default allRoutes :: (Bounded route, Enum route) => model -> [route] Source #

Instances

Instances details
Ema () () Source #

The unit model is useful when using Ema in pure fashion (see Ema.runEmaPure) with a single route (index.html) only.

Instance details

Defined in Ema.Class

Methods

encodeRoute :: () -> () -> FilePath Source #

decodeRoute :: () -> FilePath -> Maybe () Source #

allRoutes :: () -> [()] Source #

Ema UTCTime Route Source # 
Instance details

Defined in Ema.Example.Ex03_Clock

Ema Model Route Source # 
Instance details

Defined in Ema.Example.Ex02_Basic

newtype Slug Source #

An URL path is made of multiple slugs, separated by /

Constructors

Slug 

Fields

Instances

Instances details
Eq Slug Source # 
Instance details

Defined in Ema.Route.Slug

Methods

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

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

Data Slug Source # 
Instance details

Defined in Ema.Route.Slug

Methods

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

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

toConstr :: Slug -> Constr #

dataTypeOf :: Slug -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Slug Source # 
Instance details

Defined in Ema.Route.Slug

Methods

compare :: Slug -> Slug -> Ordering #

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

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

(>) :: Slug -> Slug -> Bool #

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

max :: Slug -> Slug -> Slug #

min :: Slug -> Slug -> Slug #

Show Slug Source # 
Instance details

Defined in Ema.Route.Slug

Methods

showsPrec :: Int -> Slug -> ShowS #

show :: Slug -> String #

showList :: [Slug] -> ShowS #

IsString Slug Source # 
Instance details

Defined in Ema.Route.Slug

Methods

fromString :: String -> Slug #

Generic Slug Source # 
Instance details

Defined in Ema.Route.Slug

Associated Types

type Rep Slug :: Type -> Type #

Methods

from :: Slug -> Rep Slug x #

to :: Rep Slug x -> Slug #

ToJSON Slug Source # 
Instance details

Defined in Ema.Route.Slug

FromJSON Slug Source # 
Instance details

Defined in Ema.Route.Slug

type Rep Slug Source # 
Instance details

Defined in Ema.Route.Slug

type Rep Slug = D1 ('MetaData "Slug" "Ema.Route.Slug" "ema-0.2.0.0-43Q8o53HdSb5nkEd0OygUk" 'True) (C1 ('MetaCons "Slug" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSlug") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

decodeSlug :: Text -> Slug Source #

Decode an URL component into a Slug using Encode

encodeSlug :: Slug -> Text Source #

Encode a Slug into an URL component using Encode

routeUrlWith :: forall r model. Ema model r => UrlStrategy -> model -> r -> Text Source #

Return the relative URL of the given route

As the returned URL is relative, you will have to either make it absolute (by prepending with /) or set the `base` URL in your HTML head element.

routeUrl :: forall r model. Ema model r => model -> r -> Text Source #

emaErrorHtmlResponse :: Text -> LByteString Source #

A basic error response for displaying in the browser

runEmaPure Source #

Arguments

:: (Action -> LByteString)

How to render a route

-> IO () 

Pure version of runEmaWith (i.e with no model).

Due to purity, there is no impure state, and thus no time-varying model. Neither is there a concept of route, as only a single route (index.html) is expected, whose HTML contents is specified as the only argument to this function.

runEma Source #

Arguments

:: forall model route. (Ema model route, Show route) 
=> (Action -> model -> route -> Asset LByteString)

How to render a route, given the model

-> (forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Action -> LVar model -> m ())

A long-running IO action that will update the model LVar over time. This IO action must set the initial model value in the very beginning.

-> IO () 

Convenient version of runEmaWith that takes initial model and an update function. You typically want to use this.

It uses race_ to properly clean up the update action when the ema thread exits, and vice-versa.

runEmaWithCli Source #

Arguments

:: forall model route. (Ema model route, Show route) 
=> Cli 
-> (Action -> model -> route -> Asset LByteString)

How to render a route, given the model

-> (forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Action -> LVar model -> m ())

A long-running IO action that will update the model LVar over time. This IO action must set the initial model value in the very beginning.

-> IO () 

Like runEma but takes the CLI action

Useful if you are handling CLI arguments yourself.