Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Format
- data Asset a
- newtype Dynamic m a = Dynamic (a, (a -> m ()) -> m ())
- fromPrism_ :: Prism_ s a -> Prism' s a
- toPrism_ :: Prism' s a -> Prism_ s a
- class IsRoute r where
- type RouteModel r :: Type
- routePrism :: RouteModel r -> Prism_ FilePath r
- routeUniverse :: RouteModel r -> [r]
- data UrlStrategy
- routeUrlWith :: HasCallStack => UrlStrategy -> Prism' FilePath r -> r -> Text
- routeUrl :: HasCallStack => Prism' FilePath r -> r -> Text
- type EmaStaticSite r = (EmaSite r, SiteOutput r ~ Asset LByteString)
- class IsRoute r => EmaSite r where
- type SiteArg r :: Type
- type SiteOutput r :: Type
- siteInput :: forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Some Action -> SiteArg r -> m (Dynamic m (RouteModel r))
- siteOutput :: forall m. (MonadIO m, MonadLoggerIO m) => Prism' FilePath r -> RouteModel r -> r -> m (SiteOutput r)
- emaErrorHtmlResponse :: Text -> LByteString
- runSite :: forall r. (Show r, Eq r, EmaStaticSite r) => SiteArg r -> IO [FilePath]
- runSite_ :: forall r. (Show r, Eq r, EmaStaticSite r) => SiteArg r -> IO ()
- runSiteWithCli :: forall r. (Show r, Eq r, EmaStaticSite r) => Cli -> SiteArg r -> IO (RouteModel r, DSum Action Identity)
Documentation
The format of a generated asset.
Html | Html assets are served by the live server with hot-reload |
Other | Other assets are served by the live server as static files. |
The type of assets that can be bundled in a static site.
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
Functor Asset Source # | |
Generic (Asset a) Source # | |
Show a => Show (Asset a) Source # | |
Eq a => Eq (Asset a) Source # | |
Ord a => Ord (Asset a) Source # | |
type Rep (Asset a) Source # | |
Defined in Ema.Asset type Rep (Asset a) = D1 ('MetaData "Asset" "Ema.Asset" "ema-0.10.0.0-IvDsUicoMaZ9ZiKA06zERq" 'False) (C1 ('MetaCons "AssetStatic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "AssetGenerated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Format) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
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
.
Dynamic (a, (a -> m ()) -> m ()) |
Instances
(MonadUnliftIO m, MonadLogger m) => Applicative (Dynamic m) Source # | |
Functor (Dynamic m) Source # | |
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.
type RouteModel r :: Type Source #
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
data UrlStrategy Source #
How to produce URL paths from routes
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
routeUrlWith :: HasCallStack => UrlStrategy -> Prism' FilePath r -> r -> Text Source #
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, perSiteOutput
) 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.
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.
type SiteOutput r = Asset LByteString
:: forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) | |
=> Some Action | |
-> SiteArg r | The value passed by the programmer to |
-> m (Dynamic m (RouteModel r)) | Time-varying value of the model. If your model is not time-varying, use
|
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
emaErrorHtmlResponse :: Text -> LByteString Source #
A basic error response for displaying in the browser
:: forall r. (Show r, Eq r, EmaStaticSite r) | |
=> SiteArg r | The input required to create the |
-> 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.