1
1
mirror of https://github.com/srid/ema.git synced 2024-11-29 09:25:14 +03:00

Remove Blaze helper; all helpers now gone.

This commit is contained in:
Sridhar Ratnakumar 2022-02-04 19:56:21 -05:00
parent f65e2b1b73
commit 14a069027e
16 changed files with 73 additions and 164 deletions

View File

@ -7,6 +7,7 @@
- `Ema.Helpers.PathTree` moved to separate package *pathtree*.
- `Ema.Helpers.FileSystem` moved to separate package *unionmount*.
- `Ema.Helpers.Markdown` moved to separate package *commonmark-simple*.
- `Ema.Helpers.Blaze` is no more. See `ema-template` if you need a ready made template using blaze HTML and TailwindCSS.
## 0.4.0.0 -- 2022-01-19

View File

@ -17,13 +17,13 @@ When switching to a new route or when receiving the new HTML, Ema uses [morphdom
### Haskell reload
Finally, hot reload on _code_ changes are supported via [ghcid](https://github.com/ndmitchell/ghcid). The [template repo](https://github.com/srid/ema-template)'s `bin/run` script uses ghcid underneath. Any HTML DSL (like blaze-html -- as used by the [Blaze helper](guide/helpers/blaze.md)) or CSS DSL automatically gets supported for hot-reload. If you choose to use a file-based HTML template language, you can enable hot-reload on template change using the [`unionmount` library](guide/helpers/filesystem.md).
Finally, hot reload on _code_ changes are supported via [ghcid](https://github.com/ndmitchell/ghcid). The [template repo](https://github.com/srid/ema-template)'s `bin/run` script uses ghcid underneath. Any HTML DSL (like `blaze-html`) or CSS DSL automatically gets supported for hot-reload. If you choose to use a file-based HTML template language, you can enable hot-reload on template change using the [[filesystem|`unionmount` library]].
Note that if your application makes use of threads, it is important to setup cleanup handlers so that `ghcid` doesn't leave [ghost](https://stackoverflow.com/q/24999636/55246) processes behind. Helpers like [`race_`](https://hackage.haskell.org/package/async-2.2.3/docs/Control-Concurrent-Async.html#v:race_) will do this automatically (incidentally it is used by `runEma` for running the user IO action).
### Data reload
For anything outside of the Haskell code, your code becomes responsible for monitoring and updating the model [LVar](concepts/lvar.md). The [`unionmount` library](guide/helpers/filesystem.md) already provides utilities to facilitate this for monitoring changes to files and directories.
For anything outside of the Haskell code, your code becomes responsible for monitoring and updating the model [LVar](concepts/lvar.md). The [[filesystem|`unionmount` library]] already provides utilities to facilitate this for monitoring changes to files and directories.
## Handling errors

View File

@ -4,7 +4,7 @@ order: 3
# Slug
:::{.note}
Note that the initial version of Ema used Slug in its routing system, but not anymore in the latest version. The Slug type is still left in the library for using as a [[helpers|helper]].
Note that the initial version of Ema used Slug in its routing system, but not anymore in the latest version. The Slug type is still left in the library for using as a helper.
:::
A slug is a component of a URL or file path. In an _URL_ like `/foo/bar`, there are two _slugs_: "foo" and "bar". URLs (as well as filepaths) can therefore be represented as lists of slugs (`[Slug]`).

View File

@ -10,4 +10,4 @@ After having familiarized yourself with Ema by following the [earlier section](s
* [Working with routes](guide/routes.md) -- [Unless you site has a single page (`index.html`), you will need to manage a set of routes]{.item-intro}
* [Defining Ema instance](guide/class.md) -- [Constrain your `model` and `route` to work with static sites]{.item-intro}
* [Rendering HTML](guide/render.md) -- [You could use plain strings to build HTML, or use templates, or use one of the delightful Haskell DSLs]{.item-intro}
* [Helpers](guide/helpers.md) -- [Bring Your Own Libraries, or choose from existing helpers]{.item-intro}
* [[howto]] -- [How to do common static-site things]{.item-intro}

View File

@ -1,10 +0,0 @@
---
order: 5
---
# Howto
Beyond the model and route types, Ema leaves it up to you as to how to develop your site. Here are some common aspects of writing a static site:
* [Blaze HTML DSL](guide/helpers/blaze.md) -- [Use blaze-html with Tailwind CSS]{.item-intro}
* [Working with files](guide/helpers/filesystem.md) -- [Use `unionmount` to support hot-reload on files]{.item-intro}
* [Converting Markdown](guide/helpers/markdown.md) -- [Pointers on how to work with Markdown files]{.item-intro}

View File

@ -1,27 +0,0 @@
---
order: 1
---
# Using Blaze HTML & Tailwind
## Tailwind 2.0
The `Ema.Helper.Blaze` module provides a `twindLayout` function that uses [twind](https://twind.dev/) shim that is used in the statically generated site, and otherwise uses Tailwind CSS from CDN in the dev server mode. This helper is for those that **use [Tailwind CSS](https://tailwindcss.com/) in conjunction with [blaze-html](https://hackage.haskell.org/package/blaze-html) DSL**.
To use the layout helper in your [render](guide/render.md) function:
```haskell
render :: Some Ema.CLI.Action -> MyModel -> MyRoute -> Asset LByteString
render emaAction model route = do
AssetGenerated Html $
Blaze.twindLayout emaAction (H.title "My site" >> H.base ! A.href "/") $ do
H.p "Hello world"
```
## Tailwind 3.0
> **Note** that because the above [twind JS shim](https://twind.dev/handbook/the-shim.html) is used to support Tailwind styles your site will not render properly on web browsers with JavaScript disabled if you use this helper; it might also have trouble interoperating with other JS initializers on the site. See [this issue](https://github.com/srid/ema/issues/20) for upcoming alternatives.
For new Ema sites, it is recommended to use Tailwind 3.0 both in live server and static site generation. See [ema-template](https://github.com/srid/ema-template) for an approach to this.[^pr]
[^pr]: [Here](https://github.com/srid/ema-template/pull/16) is the specific PR making this change.

View File

@ -26,7 +26,7 @@ runEma render $ \_act model ->
liftIO $ threadDelay $ 1 * 1000000
```
In this contrived example ([full code here](https://github.com/srid/ema/blob/master/src/Ema/Example/Ex02_Clock.hs)), we are using `UTCTime` as the model. We set the initial value using `LVar.set`, and then continually update the current time every second. Every time the model gets updated, the web browser will [hot reload](concepts/hot-reload.md) to display the up to date value. For the `BlogPosts` model, you would typically use [fsnotify](https://hackage.haskell.org/package/fsnotify) to monitor changes to the underlying Markdown files, or even better use [the unionmount library](guide/helpers/filesystem.md).
In this contrived example ([full code here](https://github.com/srid/ema/blob/master/src/Ema/Example/Ex02_Clock.hs)), we are using `UTCTime` as the model. We set the initial value using `LVar.set`, and then continually update the current time every second. Every time the model gets updated, the web browser will [hot reload](concepts/hot-reload.md) to display the up to date value. For the `BlogPosts` model, you would typically use [fsnotify](https://hackage.haskell.org/package/fsnotify) to monitor changes to the underlying Markdown files, or even better use [[filesystem|the `unionmount` library]].
## Advanced tips

View File

@ -13,7 +13,7 @@ render model route =
The `AssetGenerated Html` tells Ema that you are generating HTML content, which will be appropriately handled by the [[hot-reload]] of the live server.
Of course we want it to be real, by using our model value, as well as generate the HTML based on the route. We will also use the [blaze-html](https://hackage.haskell.org/package/blaze-html) library to make writing HTML in Haskell palatable (see also [the layout helper](guide/helpers/blaze.md)). A more realistic starting point (if not the finishing product) would be:
Of course we want it to be real, by using our model value, as well as generate the HTML based on the route. We will also use the [blaze-html](https://hackage.haskell.org/package/blaze-html) library to make writing HTML in Haskell palatable. A more realistic starting point (if not the finishing product) would be:
```haskell
render :: MyModel -> Route -> Asset ByteString
@ -41,7 +41,7 @@ Note that Ema provides a `routeUrl` helper function that serializes your route t
Spend a few moments trying to appreciate how this is *much simpler* to write than dealing with HTML template files spread across the disk as is the case with traditional static site generators. If you [choose](https://vrom911.github.io/blog/html-libraries) to go the DSL route, Haskell's type-safety now applies to your HTML as well. On top of it, Ema's [hot reload](concepts/hot-reload.md) will instantly update the dev server's browser view whenever you change your HTML (or any of the Haskell source code).
Of course when using Ema nothing prevents you from choosing to use traditional HTML templates, and you can get [hot reload](concepts/hot-reload.md) on them too with [a little bit of plumbing](guide/helpers/filesystem.md).
Of course when using Ema nothing prevents you from choosing to use traditional HTML templates, and you can get [hot reload](concepts/hot-reload.md) on them too with [[filesystem|a little bit of plumbing]].
{.last}
[Next]{.next}, you might want to peruse [the helper topics](guide/helpers.md) if you need some extra functionality provided.
[Next]{.next}, you might want to peruse [[howto]].

9
docs/howto.md Normal file
View File

@ -0,0 +1,9 @@
---
order: 5
---
# Howto
Beyond the model and route types, Ema leaves it up to you as to how to develop your site. Here are some common aspects of writing a static site:
* [[filesystem|Working with files]] -- [Use `unionmount` to support hot-reload on files]{.item-intro}
* [[markdown|Parsing Markdown]] -- [Pointers on how to work with Markdown files]{.item-intro}

View File

@ -31,4 +31,4 @@ CS.parseMarkdownWithFrontMatter @Metadata
The template repo, as well as [Emanote](https://github.com/srid/emanote) (used to generate this site), uses this helper to parse Markdown files into Pandoc AST. Consult [the template repo's source code](https://github.com/srid/ema-template/blob/master/src/Main.hs) for details.
Note that with Ema you can get [hot reload](concepts/hot-reload.md) support for your Markdown files using [the `unionmount` package](guide/helpers/filesystem.md).
Note that with Ema you can get [hot reload](concepts/hot-reload.md) support for your Markdown files using [[filesystem|the `unionmount` package]].

View File

@ -1,6 +1,6 @@
cabal-version: 2.4
name: ema
version: 0.5.3.0
version: 0.5.4.0
license: AGPL-3.0-only
copyright: 2021 Sridhar Ratnakumar
maintainer: srid@srid.ca
@ -24,10 +24,6 @@ flag with-examples
description: Include examples and their dependencies
default: True
flag with-helpers
description: Include helper modules based on blaze-html
default: True
library
-- Modules included in this executable, other than Main.
-- other-modules:
@ -64,13 +60,11 @@ library
, warp
, websockets
if (flag(with-helpers) || flag(with-examples))
if flag(with-examples)
build-depends:
, blaze-html
, blaze-markup
if flag(with-examples)
build-depends: time
, time
mixins:
base hiding (Prelude),
@ -127,10 +121,6 @@ library
Ema
Ema.CLI
if (flag(with-helpers) || flag(with-examples))
exposed-modules:
Ema.Helper.Blaze
other-modules:
Ema.App
Ema.Asset
@ -142,6 +132,7 @@ library
if flag(with-examples)
exposed-modules:
Ema.Example.Common
Ema.Example.Ex01_HelloWorld
Ema.Example.Ex02_Basic
Ema.Example.Ex03_Clock

40
src/Ema/Example/Common.hs Normal file
View File

@ -0,0 +1,40 @@
-- | Use Tailwind CSS with blaze-html? Try this module for rapid prototyping of
-- websites in Ema.
module Ema.Example.Common
( -- * Main functions
twindLayout,
)
where
import Text.Blaze.Html.Renderer.Utf8 qualified as RU
import Text.Blaze.Html5 ((!))
import Text.Blaze.Html5 qualified as H
import Text.Blaze.Html5.Attributes qualified as A
-- | A simple and off-the-shelf layout using Tailwind CSS
twindLayout :: H.Html -> H.Html -> LByteString
twindLayout h b =
layoutWith "en" "UTF-8" (tailwind2ShimCdn >> h) $
-- The "overflow-y-scroll" makes the scrollbar visible always, so as to
-- avoid janky shifts when switching to routes with suddenly scrollable content.
H.body ! A.class_ "overflow-y-scroll" $ b
where
-- A general layout
layoutWith :: H.AttributeValue -> H.AttributeValue -> H.Html -> H.Html -> LByteString
layoutWith lang encoding appHead appBody = RU.renderHtml $ do
H.docType
H.html ! A.lang lang $ do
H.head $ do
H.meta ! A.charset encoding
-- This makes the site mobile friendly by default.
H.meta ! A.name "viewport" ! A.content "width=device-width, initial-scale=1"
appHead
appBody
-- Loads full tailwind CSS from CDN (not good for production)
tailwind2ShimCdn :: H.Html
tailwind2ShimCdn =
H.link
! A.href "https://unpkg.com/tailwindcss@2/dist/tailwind.min.css"
! A.rel "stylesheet"
! A.type_ "text/css"

View File

@ -3,12 +3,10 @@ module Ema.Example.Ex02_Basic where
import Control.Concurrent (threadDelay)
import Data.LVar qualified as LVar
import Data.Some (Some (..))
import Ema (Ema (..))
import Ema qualified
import Ema.CLI qualified
import Ema.CLI qualified as CLI
import Ema.Helper.Blaze qualified as EB
import Ema.Example.Common (twindLayout)
import Text.Blaze.Html5 ((!))
import Text.Blaze.Html5 qualified as H
import Text.Blaze.Html5.Attributes qualified as A
@ -33,14 +31,14 @@ instance Ema Model Route where
main :: IO ()
main = do
void $
Ema.runEma (\act m -> Ema.AssetGenerated Ema.Html . render act m) $ \act model -> do
Ema.runEma (\_act m -> Ema.AssetGenerated Ema.Html . render m) $ \act model -> do
LVar.set model $ Model "Hello World. "
when (CLI.isLiveServer act) $
liftIO $ threadDelay maxBound
render :: Some Ema.CLI.Action -> Model -> Route -> LByteString
render emaAction model r =
EB.twindLayout emaAction (H.title "Basic site" >> H.base ! A.href "/") $
render :: Model -> Route -> LByteString
render model r =
twindLayout (H.title "Basic site" >> H.base ! A.href "/") $
H.div ! A.class_ "container mx-auto" $ do
H.div ! A.class_ "mt-8 p-2 text-center" $ do
case r of

View File

@ -11,12 +11,10 @@ module Ema.Example.Ex03_Clock where
import Control.Concurrent (threadDelay)
import Data.LVar qualified as LVar
import Data.List ((!!))
import Data.Some (Some)
import Data.Time (UTCTime, defaultTimeLocale, formatTime, getCurrentTime)
import Ema (Ema (..))
import Ema qualified
import Ema.CLI qualified
import Ema.Helper.Blaze qualified as EB
import Ema.Example.Common (twindLayout)
import Text.Blaze.Html5 ((!))
import Text.Blaze.Html5 qualified as H
import Text.Blaze.Html5.Attributes qualified as A
@ -38,15 +36,15 @@ instance Ema UTCTime Route where
main :: IO ()
main = do
void $
Ema.runEma (\act m -> Ema.AssetGenerated Ema.Html . render act m) $ \_act model ->
Ema.runEma (\_act m -> Ema.AssetGenerated Ema.Html . render m) $ \_act model ->
forever $ do
-- logDebugNS "ex:clock" "Refreshing time"
LVar.set model =<< liftIO getCurrentTime
liftIO $ threadDelay 1000000
render :: Some Ema.CLI.Action -> UTCTime -> Route -> LByteString
render emaAction now r =
EB.twindLayout emaAction (H.title "Clock" >> H.base ! A.href "/") $
render :: UTCTime -> Route -> LByteString
render now r =
twindLayout (H.title "Clock" >> H.base ! A.href "/") $
H.div ! A.class_ "container mx-auto" $ do
H.div ! A.class_ "mt-8 p-2 text-center" $ do
case r of

View File

@ -1,91 +0,0 @@
{-# LANGUAGE QuasiQuotes #-}
-- | Use Tailwind CSS with blaze-html? Try this module for rapid prototyping of
-- websites in Ema.
module Ema.Helper.Blaze
( -- * Main functions
layoutWith,
twindLayout,
-- * Tailwind official shims
tailwind2ShimCdn,
-- * Twind.dev shims
twindShimOfficial,
twindShimUnofficial,
)
where
import Data.Some (Some (Some))
import Ema.CLI qualified
import NeatInterpolation (text)
import Text.Blaze.Html.Renderer.Utf8 qualified as RU
import Text.Blaze.Html5 ((!))
import Text.Blaze.Html5 qualified as H
import Text.Blaze.Html5.Attributes qualified as A
-- | A general layout
layoutWith :: H.AttributeValue -> H.AttributeValue -> H.Html -> H.Html -> LByteString
layoutWith lang encoding appHead appBody = RU.renderHtml $ do
H.docType
H.html ! A.lang lang $ do
H.head $ do
H.meta ! A.charset encoding
-- This makes the site mobile friendly by default.
H.meta ! A.name "viewport" ! A.content "width=device-width, initial-scale=1"
appHead
appBody
-- | A simple and off-the-shelf layout using Tailwind CSS
twindLayout :: Some Ema.CLI.Action -> H.Html -> H.Html -> LByteString
twindLayout action h b =
layoutWith "en" "UTF-8" (shim >> h) $
-- The "overflow-y-scroll" makes the scrollbar visible always, so as to
-- avoid janky shifts when switching to routes with suddenly scrollable content.
H.body ! A.class_ "overflow-y-scroll" $ b
where
shim :: H.Html
shim =
case action of
Some (Ema.CLI.Generate _) ->
twindShimUnofficial
_ ->
-- Twind shim doesn't reliably work in dev server mode. Let's just use the
-- tailwind CDN.
tailwind2ShimCdn
-- | Loads full tailwind CSS from CDN (not good for production)
tailwind2ShimCdn :: H.Html
tailwind2ShimCdn =
H.link
! A.href "https://unpkg.com/tailwindcss@2/dist/tailwind.min.css"
! A.rel "stylesheet"
! A.type_ "text/css"
-- | This shim may not work with hot reload.
twindShimOfficial :: H.Html
twindShimOfficial =
H.unsafeByteString . encodeUtf8 $
[text|
<script type="module" src="https://cdn.skypack.dev/twind/shim"></script>
|]
-- | This shim does work with hot reload, but it spams console with warnings.
twindShimUnofficial :: H.Html
twindShimUnofficial = do
H.script
! A.type_ "text/javascript"
! A.src "https://cdn.jsdelivr.net/combine/npm/twind/twind.umd.min.js,npm/twind/observe/observe.umd.min.js"
$ ""
H.script ! A.type_ "text/javascript" $ twindShimUnofficialEval
where
twindShimUnofficialEval :: H.Html
twindShimUnofficialEval =
H.unsafeByteString . encodeUtf8 $
[text|
// Be silent to avoid complaining about non-tailwind classes
// https://github.com/tw-in-js/twind/discussions/180#discussioncomment-678272
console.log("ema: Twind: setup & observe")
twind.setup({mode: 'silent'})
window.emaTwindObs = twindObserve.observe(document.documentElement);
|]