ema-0.10.0.0: Static site generator library with hot reload
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ema

Synopsis

Documentation

data Format Source #

The format of a generated asset.

Constructors

Html

Html assets are served by the live server with hot-reload

Other

Other assets are served by the live server as static files.

Instances

Instances details
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 #

Show Format Source # 
Instance details

Defined in Ema.Asset

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

type Rep Format Source # 
Instance details

Defined in Ema.Asset

type Rep Format = D1 ('MetaData "Format" "Ema.Asset" "ema-0.10.0.0-IvDsUicoMaZ9ZiKA06zERq" '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
Functor Asset Source # 
Instance details

Defined in Ema.Asset

Methods

fmap :: (a -> b) -> Asset a -> Asset b #

(<$) :: a -> Asset b -> Asset a #

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 #

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 #

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 #

type Rep (Asset a) Source # 
Instance details

Defined in Ema.Asset

newtype Dynamic m a Source #

A time-varying value of type a, changing under monad m.

To create a Dynamic, supply the initial value along with a function that forever updates it using the given monadic update function.

Dynamic's can be composed using Applicative.

Constructors

Dynamic (a, (a -> m ()) -> m ()) 

Instances

Instances details
(MonadUnliftIO m, MonadLogger m) => Applicative (Dynamic m) Source # 
Instance details

Defined in Ema.Dynamic

Methods

pure :: a -> Dynamic m a #

(<*>) :: Dynamic m (a -> b) -> Dynamic m a -> Dynamic m b #

liftA2 :: (a -> b -> c) -> Dynamic m a -> Dynamic m b -> Dynamic m c #

(*>) :: Dynamic m a -> Dynamic m b -> Dynamic m b #

(<*) :: Dynamic m a -> Dynamic m b -> Dynamic m a #

Functor (Dynamic m) Source # 
Instance details

Defined in Ema.Dynamic

Methods

fmap :: (a -> b) -> Dynamic m a -> Dynamic m b #

(<$) :: a -> Dynamic m b -> Dynamic m a #

fromPrism_ :: Prism_ s a -> Prism' s a Source #

Convert a Prism_ to a Prism'.

toPrism_ :: Prism' s a -> Prism_ s a Source #

Convert a Prism' to a Prism_.

class IsRoute r where Source #

Class of Ema routes

An Ema route has a Prism' routePrism, that knows how to convert it to/from filepaths. As well as an universe function, routeUniverse, that gives all possible route values in a static site.

Both functions take the associated model, `RouteModel r`, as an argument.

Associated Types

type RouteModel r :: Type Source #

Methods

routePrism :: RouteModel r -> Prism_ FilePath r Source #

An optics Prism` that denotes how to encode and decode a route.

routeUniverse :: RouteModel r -> [r] Source #

All possible route values for the given RouteModel.

This is used in determining the pages to statically generate.

Instances

Instances details
IsRoute () Source # 
Instance details

Defined in Ema.Route.Class

Associated Types

type RouteModel () Source #

KnownSymbol fn => IsRoute (FileRoute fn) Source # 
Instance details

Defined in Ema.Route.Lib.File

Associated Types

type RouteModel (FileRoute fn) Source #

(IsRoute r, IsRoute (MultiRoute rs), RouteModel (MultiRoute rs) ~ NP I (MultiModel rs)) => IsRoute (MultiRoute (r ': rs)) Source # 
Instance details

Defined in Ema.Route.Lib.Multi

Associated Types

type RouteModel (MultiRoute (r ': rs)) Source #

Methods

routePrism :: RouteModel (MultiRoute (r ': rs)) -> Prism_ FilePath (MultiRoute (r ': rs)) Source #

routeUniverse :: RouteModel (MultiRoute (r ': rs)) -> [MultiRoute (r ': rs)] Source #

IsRoute (MultiRoute ('[] :: [Type])) Source # 
Instance details

Defined in Ema.Route.Lib.Multi

Associated Types

type RouteModel (MultiRoute '[]) Source #

(IsRoute r, KnownSymbol prefix) => IsRoute (FolderRoute prefix r) Source # 
Instance details

Defined in Ema.Route.Lib.Folder

Associated Types

type RouteModel (FolderRoute prefix r) Source #

data UrlStrategy Source #

How to produce URL paths from routes

Constructors

UrlPretty

Use pretty URLs. The route encoding "foobar.html" produces "foobar" as URL.

UrlDirect

Use filepaths as URLs. The route encoding "foobar.html" produces "foobar.html" as URL.

Instances

Instances details
FromJSON UrlStrategy Source # 
Instance details

Defined in Ema.Route.Url

Generic UrlStrategy Source # 
Instance details

Defined in Ema.Route.Url

Associated Types

type Rep UrlStrategy :: Type -> Type #

Show UrlStrategy Source # 
Instance details

Defined in Ema.Route.Url

Eq UrlStrategy Source # 
Instance details

Defined in Ema.Route.Url

Ord UrlStrategy Source # 
Instance details

Defined in Ema.Route.Url

type Rep UrlStrategy Source # 
Instance details

Defined in Ema.Route.Url

type Rep UrlStrategy = D1 ('MetaData "UrlStrategy" "Ema.Route.Url" "ema-0.10.0.0-IvDsUicoMaZ9ZiKA06zERq" 'False) (C1 ('MetaCons "UrlPretty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UrlDirect" 'PrefixI 'False) (U1 :: Type -> Type))

routeUrlWith :: HasCallStack => UrlStrategy -> Prism' FilePath r -> r -> Text Source #

Return the relative URL of the given route

Note: when using relative URLs it is imperative to set the `base` URL to your site's base URL or path (typically just /). Otherwise you must accordingly make these URLs absolute yourself.

routeUrl :: HasCallStack => Prism' FilePath r -> r -> Text Source #

Like routeUrlWith but uses UrlDirect strategy

type EmaStaticSite r = (EmaSite r, SiteOutput r ~ Asset LByteString) Source #

Like EmaSite but SiteOutput is a bytestring Asset.

class IsRoute r => EmaSite r where Source #

Typeclass to orchestrate an Ema site

Given a route r from the class of IsRoute types, instantiating EmaSite on it enables defining the site build pipeline as follows:

 SiteArg -> siteInput -> Dynamic model --[r, model]--> siteOutput
 
  • SiteArg is typically not used, but it can be used to pass command line arguments and other such settings.
  • siteInput returns a time-varying value (Dynamic) representing the data for your static site.
  • siteOutput takes this data model (oneshot value) and returns the generated content (usually HTML asset, per SiteOutput) for the given route.

Finally, `Ema.App.runSite @r arg` (where arg is of type SiteArg) is run from the main entry point to run your Ema site.

Associated Types

type SiteArg r :: Type Source #

SiteArg is typically settings from the environment (config file, or command-line arguments) that your Dynamic-producing siteInput function consumes as argument.

type SiteArg r = ()

type SiteOutput r :: Type Source #

Type of the value returned by siteOutput. Usually `Asset LByteString` but it can be anything.

Methods

siteInput Source #

Arguments

:: forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) 
=> Some Action 
-> SiteArg r

The value passed by the programmer to runSite

-> m (Dynamic m (RouteModel r))

Time-varying value of the model. If your model is not time-varying, use pure to produce a constant value.

Get the model's time-varying value as a Dynamic.

If your model is not time-varying, use pure to produce a constant value.

siteOutput :: forall m. (MonadIO m, MonadLoggerIO m) => Prism' FilePath r -> RouteModel r -> r -> m (SiteOutput r) Source #

Return the output (typically an Asset) for the given route and model.

Instances

Instances details
(EmaStaticSite r, EmaStaticSite (MultiRoute rs), SiteArg (MultiRoute rs) ~ NP I (MultiSiteArg rs), RouteModel (MultiRoute rs) ~ NP I (MultiModel rs)) => EmaSite (MultiRoute (r ': rs)) Source # 
Instance details

Defined in Ema.Route.Lib.Multi

Associated Types

type SiteArg (MultiRoute (r ': rs)) Source #

type SiteOutput (MultiRoute (r ': rs)) Source #

Methods

siteInput :: (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Some Action -> SiteArg (MultiRoute (r ': rs)) -> m (Dynamic m (RouteModel (MultiRoute (r ': rs)))) Source #

siteOutput :: (MonadIO m, MonadLoggerIO m) => Prism' FilePath (MultiRoute (r ': rs)) -> RouteModel (MultiRoute (r ': rs)) -> MultiRoute (r ': rs) -> m (SiteOutput (MultiRoute (r ': rs))) Source #

EmaSite (MultiRoute ('[] :: [Type])) Source # 
Instance details

Defined in Ema.Route.Lib.Multi

Associated Types

type SiteArg (MultiRoute '[]) Source #

type SiteOutput (MultiRoute '[]) Source #

(EmaStaticSite r, KnownSymbol prefix) => EmaSite (FolderRoute prefix r) Source # 
Instance details

Defined in Ema.Route.Lib.Folder

Associated Types

type SiteArg (FolderRoute prefix r) Source #

type SiteOutput (FolderRoute prefix r) Source #

Methods

siteInput :: (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Some Action -> SiteArg (FolderRoute prefix r) -> m (Dynamic m (RouteModel (FolderRoute prefix r))) Source #

siteOutput :: (MonadIO m, MonadLoggerIO m) => Prism' FilePath (FolderRoute prefix r) -> RouteModel (FolderRoute prefix r) -> FolderRoute prefix r -> m (SiteOutput (FolderRoute prefix r)) Source #

emaErrorHtmlResponse :: Text -> LByteString Source #

A basic error response for displaying in the browser

runSite Source #

Arguments

:: forall r. (Show r, Eq r, EmaStaticSite r) 
=> SiteArg r

The input required to create the Dynamic of the RouteModel

-> IO [FilePath] 

Run the given Ema site,

Takes as argument the associated SiteArg.

In generate mode, return the generated files. In live-server mode, this function will never return.

runSite_ :: forall r. (Show r, Eq r, EmaStaticSite r) => SiteArg r -> IO () Source #

Like runSite but discards the result

runSiteWithCli :: forall r. (Show r, Eq r, EmaStaticSite r) => Cli -> SiteArg r -> IO (RouteModel r, DSum Action Identity) Source #

Like runSite but takes the CLI action. Also returns more information.

Useful if you are handling the CLI arguments yourself.

Use "void $ Ema.runSiteWithCli def ..." if you are running live-server only.