HTML in Haskell - Haskell

Welcome to the Functional Programming Zulip Chat Archive. You can join the chat here.

TheMatten

With RebindableSyntax, HTML in Haskell can be more readable than HTML itself :big_smile: :

example :: HTML
example = html do
  #head do
    #title "This is a title"
  #body do
    "Hello World!"

    #h1 "Heading level 1"
    #h2 "Heading level 2"
    #h3 "Heading level 3"
    #h4 "Heading level 4"
    #h5 "Heading level 5"
    #h6 "Heading level 6"

    #p "Paragraph"

    #a do
      #href =: "https://www.wikipedia.org/"

      "A link to Wikipedia!"

    #input $ #type =: "text"
    #input $ #type =: "file"
    #input $ #type =: "checkbox"

    comment "This is a comment"

    #abbr do
      #id    =: "anId"
      #class =: "jargon"
      #style =: "color:purple;"
      #title =: "Hypertext Markup Language"

      "HTML"
Sridhar Ratnakumar

Looks much better, actually. Any reason this can't go in the lucid library (that rib and zulip-archive use)?

James King

:thinking: wonder if this can be interpreted from a data structure.

very neat! :smiley:

TheMatten

I will have to fiddle with this a little bit more if I want monadic do to still function properly :sweat_smile:

Sridhar Ratnakumar

There is also CSS via the clay library.

Sridhar Ratnakumar

I'd love to get a syntax like this into rib :-)

Sridhar Ratnakumar

Do attributes have to be inside the element body though? What's the rational for it?

Sridhar Ratnakumar

I mean, how about the following?

#a (#href =: "theurl" <> #title =: "some tooltip") do
  #div do
     ...
Vance Palacio

Wow that's really cool, didn't realize Haskell had something like that

TheMatten

@Sridhar Ratnakumar I found it to be nicer - but it doesn't have to be that way necessarily

TheMatten

@Vance Palacio See RebindableSyntax, OverloadedLabels, OverloadedStrings and DataKinds :slight_smile:

TheMatten

(And then some other usual stuff from "GHC Haskell")

Joel McCracken

personally i think [href "theurl", title "some tooltip"] is plenty readable

TheMatten

@Joel McCracken problem is that you have to define every possible tag and attribute in library - with labels, user can create arbitrary one, while we can still possibly check that it's a valid tag (consisting of alphanumeric characters) at compile-time

TheMatten

@Sridhar Ratnakumar should I try to integrate this with lucid?

TheMatten

element by itself in lucid:

table_ [rows_ "2"]
       (tr_ (do td_ [class_ "top",colspan_ "2",style_ "color:red"]
                    (p_ "Hello, attributes!")
                td_ "yay!"))

vs html-do

element #table [#rows =: "2"] do
  #tr do
    #td [#class =: "top", #colspan =: "2", #style =: "color:red"] do
      #p "Hello, attributes!"
    #td "yay!"
TheMatten

Without some sort of "html monad" that doesn't really make sense in context of building HTML declaratively

TheMatten

I've removed (=:) in favour of IsLabel instance:

element #table [#rows "2"] do
  #tr do
    #td [#class "top", #colspan "2", #style "color:red"] do
      #p "Hello, attributes!"
    #td "yay!"
TheMatten

Now, question is - should I integrate this interface with existing library (lucid), or should it be self-contained?

Sridhar Ratnakumar

@TheMatten Separate library, I'd think? A couple of things to note: a) not sure Chris would be open to changing the syntax of the lucid library in this manner, b) we could extend this syntax to CSS too, which means html-do could contain css-do ... as well as non-html xml documents like svg-do or rss-do.

Rib can easily switch to it, as long as this HTML monad will support including raw html somewhere inside.

Sridhar Ratnakumar

About the attributes syntax,

[#class "top", #colspan "2", #style "color:red"]

Syntactically it looks good to me, however semantically it would be better to have this be a map than a list. What happens when there are duplicate attributes? [#class "one", #class "two"]?

Sridhar Ratnakumar

(Okay, not sure about css-do -- because that's not even XML (and the clay library does a good job for now) -- but other formats like svg, and rss could definitely make use of this monadic syntax; in fact, I've been looking for one to generate RSS feeds on my website).

TheMatten

Ok - we will need to build our own pretty printer then (with sanitization and stuff)?
a) I don't expect him to - I choose to not use Monad for HTML builder and instead expose (>>) for custom behaviour through RebindableSyntax
b) Not sure if CSS is as good fit as HTML for something like this - but if we can sort out syntax of selectors, it could be useful

Sridhar Ratnakumar

It is not a monad? :thinking:

TheMatten
class Sequence x y where
  (>>) :: x -> y -> y
TheMatten
-- | 'HTMLBuilder's can be sequenced by appending more children.
instance (builder ~ HTMLBuilder, builder' ~ HTMLBuilder)
      => Sequence builder builder' where
  (>>) = (<>)

-- | We fall back to 'Monad' if type follows shape of @m a@.
instance {-# incoherent #-} (Monad m, ma ~ m a) => Sequence ma (m b) where
  (>>) = (P.>>)
TheMatten

If we want multiple formats other than HTML, this would be relaxed to:

instance (builder ~ HTMLBuilder) => Sequence builder HTMLBuilder

dropping incoherent

Sridhar Ratnakumar

I can use let bindings and things in the do block?

TheMatten

You can use let - it desugars to let .. in ..

Sridhar Ratnakumar

Also, interested in seeing how State can be used when constructing HTML. Looking forward to playing with the library!

Sridhar Ratnakumar

Hmm, because of rebinding of core operators like >>, the HTML thing should be in its own module, right? Eg, this entire renderPage function (and anything else that constructs HTML) should be on its own module: https://github.com/srid/zulip-archive/blob/641a6fa/src/Main.hs#L111-L193

Zulip Archive viewer (statically generated HTML). Contribute to srid/zulip-archive development by creating an account on GitHub.
Sridhar Ratnakumar

Even the clay Css monad cannot be used in the same module because of the rebinding? Is this a necessary limitation?

TheMatten

It doesn't have to be - you just change imports a little bit:

import Prelude hiding ((>>))
import HTML.Do
TheMatten

If you have some State, you probe it in some outer do - in same way as there's not syntax for binding inside of list literal - it doesn't make much sense

Sridhar Ratnakumar

Well, let's say you use that import. Can you define main :: IO () in that same module using do block? Wouldn't that use your Sequence's >> (instead of Monad's >>)?

TheMatten

No - that's the trick :slight_smile:

TheMatten

I actually test this to make sure it always works - https://gitlab.com/thematten/html-do

TheMatten

Normally, type of do notation is at least m a - that never unifies with HTMLBuilder, and so we can make use of it

Sridhar Ratnakumar

I wonder how that works. IIUC, the compiler desugars do blocks using >> (and >>=), but Monad's >> is not in scope.

Sridhar Ratnakumar

Ah, because you defined an instance for it.

Sridhar Ratnakumar

In order to switch to your library, I would be replacing (among others) lucid's toHtmlRaw :: String -> Html () with the corresponding function from html-do: https://github.com/srid/rib/blob/0351061/src/Rib/Parser/Pandoc.hs#L69

Haskell library for writing your own static site generator - srid/rib
TheMatten

Question is - is all you need one-directional HTML emitting? Because then HTMLBuilder could possibly just build final Text directly

Sridhar Ratnakumar

Bidirectional. There is also Lucid.renderText that needs replacing: https://github.com/srid/rib/blob/251577b/src/Rib/Shake.hs#L138

Haskell library for writing your own static site generator - srid/rib
Sridhar Ratnakumar

(It ultimately goes to a file on disk, so doesn't have to be pretty, but ideally should be small and valid)

TheMatten

So you're reading some HTML too?

Sridhar Ratnakumar

toHtmlRaw is needed when you get raw HTML from some source beyond your control (such as Pandoc's renderer, or the zulip API returning message raw HTML), and would like to incorporate it in your HTML syntactic monad.

TheMatten

Just to make sure we understand each other - HTMLBuilder isn't a Monad, it's a Monoid and Sequence allows us to use do notation for appending it's values, getting this nice syntax above as a result. This allows for easy HTML construction - parsing HTML is orthogonal problem, but it could be done by lib too, possibly using some mature dependency.

Sridhar Ratnakumar

Gotcha. It is just monadic syntax (without being a monad). Or maybe we should call it do-syntax.

Sridhar Ratnakumar

Can Blaze be used for the parsing HTML problem? Like lucid already does: https://github.com/chrisdone/lucid/blob/45a01bb14b491f376f498cd5eba8c3944a129681/src/Lucid/Base.hs#L247-L251

Clear to write, read and edit DSL for writing HTML - chrisdone/lucid
Sridhar Ratnakumar

That is, use Blaze's HTML datastructure (but not its monad) for representing the underlying HTML?

TheMatten

I guess the only reason for using Monad for HTML building is that it does not require RebindableSyntax
If RebindableSyntax is a problem, it could be changed - but to me it feels like a roundabout solution, basically being Writer for no good reason

We can use whatever works well I guess :big_smile:

TheMatten

Okay, let's use blaze-html then - last question is if you're okay with reasoning behind Sequence or if HTMLBuilder should be "useless monad" too to avoid RebindableSyntax :slight_smile:

Sridhar Ratnakumar

(though the blaze datastructure is not general enough to incorporate any xml document)

Sridhar Ratnakumar

I don't really know about the last question - I guess it depends on how it would work in practice. So far, all HTML construction I've done have been in pure functions, and that includes the use of State, which I needed to build some state while building the rows of a table. But because lucid used HtmlT monad, I ended up using StateT.

Sridhar Ratnakumar

It seems to me that as an user of your library, it shouldn't matter - unless a real monad is needed when constructing HTML? Is that even a possible use case? (I certainly don't imagine someone doing liftIO in the midst of creating HTML tree)

TheMatten

I imagine that if one constructs HTML in some context, they build expression in same way as any other normal value:

do a <- b
   c <- d
   pure $ html do ..
Sridhar Ratnakumar

Can't think of what b and d would be, aside from State's get and put.

Sridhar Ratnakumar

If b and d are computed independent of the HTML, they may as well be passed as (pure) arguments to the UI function.

Sridhar Ratnakumar

Wait, can you even use State with your Sequence-based do syntax?

TheMatten

Can it be dependent on HTML in any way?
You can use do syntax as normally - custom HTMLBuilder instance is only selected when you use custom combinators

Sridhar Ratnakumar

See this example where I use State in the midst of HTML construction:

renderBirdsEyeView :: Monad m => Calendar (DMap Tracking Identity) -> HtmlT m ()
renderBirdsEyeView entries = do
  with table_ [class_ "ui very basic unstackable compact table birdseye"] $ do
    thead_ $ tr_ $ do
      with th_ [class_ "two wide"] ""
      forM_ factors $ \a ->
        with th_ [class_ "two wide"] $ factorTitle a
    tbody_ $ do
      withHtmlT (fmap fst . flip runStateT mempty)
        $ forM_ (reverse entries)
        $ renderEntry
  where
    withHtmlT f = HtmlT . f . runHtmlT
    renderEntry :: (Monad m, MonadState (Map Factor Int) m) => (Day, DMap Tracking Identity) -> HtmlT m ()
    renderEntry (day, tracks) =
      tr_ $ do
        let entry = maybe (error "No activity") runIdentity $ DMap.lookup Tracking_Activity tracks
        -- feelings = runIdentity <$> DMap.lookup Tracking_Feeling tracks
        with td_ [class_ "day"] $ do
          let dayS = formatTime defaultTimeLocale "%m/%d" day
          renderMood (skin entry)
            $ with a_ [href_ "./"]
            $ toHtml dayS
        forM_ factors $ \factor -> td_ $
          renderFactor tracks factor >>= \case
            Just True -> do
              fmap (Map.lookup factor) get >>= \case
                Just 6 -> do
                  modify $ Map.insert factor 0
                  "7"
                Just n ->
                  modify $ Map.insert factor (n + 1)
                Nothing ->
                  modify $ Map.insert factor 1
            Just False -> do
              modify $ Map.delete factor
            Nothing ->
              pure ()
    acts = [Ate boneMarrow, Ate costcoScallop, Ate (D Cheese), WentOut]
    factors = [Factor_Mood, Factor_Meals, Factor_Coffee, Factor_Egg, Factor_Spice] <> fmap Factor_DidAct acts
Sridhar Ratnakumar

Basically it builds a table, and for every 7th row if a particular food item had been consumed every day non-stop, puts the string "7" in that table cell.

Sridhar Ratnakumar

Oh, and notice the use of >>=. So I guess monad is useful after all ...

Sridhar Ratnakumar

That function is defined as renderFactor :: Monad m => DMap Tracking Identity -> Factor -> HtmlT m (Maybe Bool)

Sridhar Ratnakumar

(Idle curiosity: how would this all look if we were to use polysemy instead?)

TheMatten

Ah, so monadic builder makes sense for making effectful combinators without having to use <$>/<*> I guess

TheMatten

In polysemy it would be renderBirdsEyeView :: Member HTML r => Calendar (DMap Tracking Identity) -> Sem r () with code roughly the same I guess

TheMatten

Okay - so at the end, let's say we build interface that allows something like:

renderBirdsEyeView entries = element
  #table [#class "ui very basic unstackable compact table birdseye"] do
    #thead $ #tr do
      #th [#class "two wide"] ""
      forM_ factors \a ->
        #th [#class "two wide"] $ factorTitle a
    #tbody $ fmap fst $ runState mempty
        $ forM_ (reverse entries)
        $ renderEntry
Sridhar Ratnakumar

What would be the type of the second argument to runState here?

TheMatten

Sem (State (Map ..) : r) ()

TheMatten

Now there's version using blaze-markup in https://gitlab.com/thematten/html-do/-/tree/blaze-html - see HTML.DoSpec for examples

TheMatten

You can use Text.Blaze.Renderer.Pretty.renderMarkup to print them

TheMatten

Oh, I need to add raw

TheMatten

And I'll probably add Prelude.HTML.Do that selects right (>>) for you

Sridhar Ratnakumar

Nice. Once there is both 'raw2html' and 'html2raw' - we can try integrating it with rib ...

TheMatten

You want raw2html for embedding stringly pieces of HTML or for actual parsing?

Sridhar Ratnakumar

Just to embed it in the HTML do thingy. Think of putting the raw Zulip message HTML coming from their API somewhere in your existing HTML do syntax.

Sridhar Ratnakumar

(No need to actually parse it; but ultimately the raw HTML should appear as expected in the final 'rendered' HTML text)

TheMatten

Done - I'm now pretty happy with it's interface (though threading Sem through was not feasible - let's just bind effects upfront before using html syntax):
https://gitlab.com/thematten/html-do

TheMatten

Added few more small changes
Haha, support for html-do in rib may actually end up being reason for me to use it in the future :big_smile:
I may later find some time to do css-do too if it turns out to work nicely :slight_smile:

TheMatten

When it comes to CSS, would something like:

"strong" do
  "color" "red"

"div.menu-bar li:hover > ul" do
  "display" "block"

be useful in any way?

TheMatten

We can't use labels, because they can't contain - - this looks a little bit stringy, plus I guess in CSS there's not that much interest in filling values dynamically

TheMatten

@Sridhar Ratnakumar :up:

Sridhar Ratnakumar

The CSS stuff should disallow invalid combinations. Like display: 2px. Clay does this. In Clay you have to use strings for selectors like "div.menu-bar", but Clay also allows plain display function.

Sridhar Ratnakumar

Example: https://github.com/srid/website/blob/a0e8db4/src/Website/View/CSS.hs

Source for my website. Contribute to srid/website development by creating an account on GitHub.
TheMatten

I guess with CSS being more rigid and "typed", approach with labels does not make that much sense - you have to define all the properties in library anyway
Are there some pain points in clay that could be solved with new interface, or is it good enough to stay with it?

Sridhar Ratnakumar

I think Clay is good enough.

Sridhar Ratnakumar

Rib might need a small refactoring to avoid assuming HTML builder, but to begin with https://github.com/srid/rib-sample/blob/7ce0bd6/src/Main.hs#L93-L119 can be replaced with your HTML-do stuff while the Rib.writeHtml above is replaced with Rib.writeFileCached . yourRenderFunction.

(In case if you are interested in poking around; otherwise I will get to it later)

Sample site for the Rib static site generator. Contribute to srid/rib-sample development by creating an account on GitHub.
Sridhar Ratnakumar

(I also need to get rid of , or improve, theRib.{load,write}Target ugliness using this opportunity)

Sridhar Ratnakumar

Hacking on this, if anybody want to pair (tmate)

Sridhar Ratnakumar

@TheMatten Think I've found a problem. You can't use a monad as argument to those label thingies? For eg.,

#div $ forM_ srcs $ \src ->
  #li [#class "pages"] $ do
     [...]

gives:

    • Couldn't match type ‘m0 ()’ with ‘HTML’
        arising from the overloaded label ‘#div’
 ```
Sridhar Ratnakumar

To reproduce, follow the README in the html-do branch of this repo: https://github.com/srid/rib-sample/tree/html-do

Sample site for the Rib static site generator. Contribute to srid/rib-sample development by creating an account on GitHub.
TheMatten

Hmmmm, let's just put this thing on top of Lucid - I won't be able to avoid something like HtmlT if we want monadic HTML

TheMatten

(BTW, I didn't forget about this - once I resolve some inference problems I will push lucid version out :slight_smile: )

TheMatten

So I forgot about this after all :joy: - but QualifiedDo was accepted and may come in 8.12, so we won't need ugly tricks with RebindableSyntax to use do blocks

The proposal has been accepted; the following discussion is mostly of historic interest. This proposal introduces a mechanism to override the meaning of a do-notation block (a bit like with -XRebi...
Sridhar Ratnakumar

@TheMatten Any news on your HTML DSL attempts?

Sridhar Ratnakumar

(btw, this topic comes up in 1st page of google when searching for haskell html dsl :grinning:)

TheMatten

So we have QualifiedDo now and thus we could do something like:

module HTML where
  data HTML
  (>>) :: HTML -> HTML -> HTML
  ...
module Example where
  import HTML qualified as H
  example = H.do
    H.div [#class "foo"] $ H.form [] do
      "Some Form"
      H.input [#type "text", #name "Input"]
      H.input [#type "submit", #value "Submit"]

At the same time, I was thinking a little bit about possible solutions and I think I like the idea of special syntax for this purpose, maybe similar to HSX, that could be checked for correctness at compile-time and would interact well with dynamic client-side functionality
Basically, I would like to see something like JSX/Angular done well, possibly paired with some FRP-like or Shpadoinkle-like framework

Sridhar Ratnakumar

HSX can be written pretty much like normal HTML. You can write an HSX expression inside your Haskell code by wrapping it with [hsx|YOUR HSX CODE|]. HSX expressions are just a syntax for blaze HTML and thus are automatically escaped as described in the blaze documentation.

Because the HSX is parsed, you will get a syntax error when you type in invalid HTML. https://ihp.digitallyinduced.com/Guide/hsx.html

Sridhar Ratnakumar

https://github.com/digitallyinduced/ihp/blob/master/IHP/HtmlSupport/Parser.hs

🔥 The fastest way to build type safe web apps. IHP is a new batteries-included web framework optimized for longterm productivity and programmer happiness - digitallyinduced/ihp