Hello, when the somePage does not contain any arguments, it builds. But when I try to customize this page and use a User argument, it fails on h2_ line. Why? It seems to be a so trivial thing - to print a custom text, but it fails.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
import Lucid
data User = User
{ name :: Text
, email :: Text
} deriving (Eq, Show, Generic)
somePage :: User -> Html ()
somePage (User name email) = html_ $ do
head_ $ do
title_ "Some Page"
body_ $ do
h2_ "This single line builds"
h2_ ("But this line does not build" ++ unpack username)
The build error is:
Couldn't match type: HtmlT Data.Functor.Identity.Identity a0
with: [Char]
arising from a functional dependency between:
constraint ‘Term [Char] (HtmlT Data.Functor.Identity.Identity a0)’
arising from a use of ‘h2_’
instance ‘Term (HtmlT m a) (HtmlT m a)’ at <no location info>
Lucid’s Html type has an instance of IsString
, which means that when used together with OverloadedStrings
, any string literal in your program might be inferred to have type Html ()
. Usually this makes programs simpler, but sometimes you get subtle issues where the inferred types change with small changes of your program, as in your example:
-- the literal here is inferred to be html
h2_ ("This single line builds" :: Html ())
-- but this literal must be String to use (++)
h2_ ((("But this line does not build" :: String) ++
unpack username) :: String)
In the first line, the literal must have type Html ()
to type check (but if you turn OverloadedStrings
off, it won’t).
In your second line, you use (++)
, which operates on String
— so the compiler will instead infer that this literal must have type String
, and since the result of (++)
also has type String
, but since h2_
expects html, this is a type error.
So in this case the solution is to convert from String
to Html ()
manually:
h2_ ("This single line builds" :: Html ())
h2_ (toHtml ("But this line does not build" ++ unpack username))
should type check.
3 Likes