> I've got a stylistic question about Haskell.
> What's the best way to add optional arguments to a
> embedded DSL?
> 
[..]
> --------------------------------------------------
> (1) Combinators takes a list of attributes.
>    Now we have
> 
>    h1 :: [HtmlAttr] -> Html -> Html
> 
>    and might write
> 
>         h1 [align "right"] (stringToHtml "This is a Header")
> 
>    but now there are lots of [] scattered needlessly all over
>    the code.
>    
> --------------------------------------------------

This is (as Tommy Thorn has already noted) what TkGofer and TclHaskell
use at present, and it seems quite convenient.  One clever thing is
done as well, to prevent illegal attributes being passed:

class Has_alt w where
  alt :: String -> Conf w
  alt s = ...

class Has_align w where
  align :: Alignment -> Conf w
  align a = ...

instance Has_alt IMG
instance Has_align IMG
instance Has_align H1

img :: URL    -> [Conf IMG] -> HTML
h1  :: String -> [Conf H1]  -> HTML

img "purple.gif" [alt "purple picture", align Right]   -- OK
h1 "My heading" [align Left]                           -- OK
h1 "My illegal heading" [align Left, alt "illegal"]    -- type error


This is quite a cunning trick.

An override can be provided, too, as follows:

(%!) :: String -> String -> Conf w
tag %! val = ...

h1 "My illegal heading" [align Left, "alt" %! "illegal"]  -- OK


HTH.

--KW 8-)


Reply via email to