| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ema
Synopsis
- data Format
- data Asset a
- class Ema model route | route -> model where
- encodeRoute :: model -> route -> FilePath
- decodeRoute :: model -> FilePath -> Maybe route
- allRoutes :: model -> [route]
- newtype Slug = Slug {}
- decodeSlug :: Text -> Slug
- encodeSlug :: Slug -> Text
- unicodeNormalize :: Text -> Text
- data UrlStrategy
- routeUrlWith :: forall r model. Ema model r => UrlStrategy -> model -> r -> Text
- routeUrl :: forall r model. Ema model r => model -> r -> Text
- emaErrorHtmlResponse :: Text -> LByteString
- runEmaPure :: (Some Action -> LByteString) -> IO ()
- runEma :: forall model route b. (Ema model route, Show route) => (Some Action -> model -> route -> Asset LByteString) -> (forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Some Action -> LVar model -> m b) -> IO (Either b (DSum Action Identity))
- runEmaWithCli :: forall model route b. (Ema model route, Show route) => Cli -> (Some Action -> model -> route -> Asset LByteString) -> (forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Some Action -> LVar model -> m b) -> IO (Either b (DSum Action Identity))
Documentation
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
| Eq a => Eq (Asset a) Source # | |
| Ord a => Ord (Asset a) Source # | |
| Show a => Show (Asset a) Source # | |
| Generic (Asset a) Source # | |
| type Rep (Asset a) Source # | |
Defined in Ema.Asset type Rep (Asset a) = D1 ('MetaData "Asset" "Ema.Asset" "ema-0.4.0.0-3YQh6eWcUzi6sUL0eldA5W" '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))) | |
class Ema model route | route -> model where Source #
Enrich a model to work with Ema
Minimal complete definition
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.
An URL path is made of multiple slugs, separated by /
Instances
| Eq Slug Source # | |
| Data Slug Source # | |
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 # 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 # | |
| Show Slug Source # | |
| IsString Slug Source # | |
Defined in Ema.Route.Slug Methods fromString :: String -> Slug # | |
| Generic Slug Source # | |
| ToJSON Slug Source # | |
Defined in Ema.Route.Slug | |
| FromJSON Slug Source # | |
| type Rep Slug Source # | |
Defined in Ema.Route.Slug | |
unicodeNormalize :: Text -> Text Source #
data UrlStrategy Source #
Instances
| Eq UrlStrategy Source # | |
Defined in Ema.Route | |
| Ord UrlStrategy Source # | |
Defined in Ema.Route Methods compare :: UrlStrategy -> UrlStrategy -> Ordering # (<) :: UrlStrategy -> UrlStrategy -> Bool # (<=) :: UrlStrategy -> UrlStrategy -> Bool # (>) :: UrlStrategy -> UrlStrategy -> Bool # (>=) :: UrlStrategy -> UrlStrategy -> Bool # max :: UrlStrategy -> UrlStrategy -> UrlStrategy # min :: UrlStrategy -> UrlStrategy -> UrlStrategy # | |
| Show UrlStrategy Source # | |
Defined in Ema.Route Methods showsPrec :: Int -> UrlStrategy -> ShowS # show :: UrlStrategy -> String # showList :: [UrlStrategy] -> ShowS # | |
| FromJSON UrlStrategy Source # | |
Defined in Ema.Route | |
routeUrlWith :: forall r model. Ema model r => UrlStrategy -> model -> r -> Text Source #
emaErrorHtmlResponse :: Text -> LByteString Source #
A basic error response for displaying in the browser
Arguments
| :: (Some 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.
Arguments
| :: forall model route b. (Ema model route, Show route) | |
| => (Some Action -> model -> route -> Asset LByteString) | How to render a route, given the model |
| -> (forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Some Action -> LVar model -> m b) | A long-running IO action that will update the |
| -> IO (Either b (DSum Action Identity)) |
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.
Arguments
| :: forall model route b. (Ema model route, Show route) | |
| => Cli | |
| -> (Some Action -> model -> route -> Asset LByteString) | How to render a route, given the model |
| -> (forall m. (MonadIO m, MonadUnliftIO m, MonadLoggerIO m) => Some Action -> LVar model -> m b) | A long-running IO action that will update the |
| -> IO (Either b (DSum Action Identity)) |
Like runEma but takes the CLI action
Useful if you are handling CLI arguments yourself.