I've got a stylistic question about Haskell.
What's the best way to add optional arguments to a
embedded DSL?

For example, say I've got an library of HTML combinators.
To represent

        <H1>This is a Header</H1>

you might write

        h1 (stringToHtml "This is a Header")

The types of the functions are

h1 :: Html -> Html
stringToHtml :: String -> Html

Looks OK, but what about if you want this header
right aligned? I can see three ways.

--------------------------------------------------
(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.
   
--------------------------------------------------
(2) Combinators that take arguments have different names.
    So you might have

    h1 :: Html -> Html
    h1' :: [HtmlAttr] -> Html -> Html

--------------------------------------------------
(3) Have an "inherit attributes combinator".

    addAttrs :: [HtmlAttr] -> Html -> Html

    So we might write

        (h1 (stringToHtml "This is a Header")) 
                `addAttrs` [align "right"]

    This can be cleaned up a bit. define

    (<<) :: (Html -> Html) -> [HtmlAttr] -> (Html -> Html)
    fn << attr = \ html -> fn html `addAttrs` [attr]

    We can now write

        (h1 << align "right") (stringToHtml "This is a Header")

    or

        h1 << align "right" $ stringToHtml "This is a Header"

    [You could also write

        h1 <| align "right" |> stringToHtml "This is a Header"
        
    if you had <| = << and |> = $, with the right prec.]

    However, We're now playing games with syntax, and have
    perhaps lost the thread. Working out when to put
    <| and |>; only where the first argument is a function,
    is a lot easier to get lost that always putting a [].
    And the error messages are now obfuscated.

--------------------------------------------------

Has anyone put any thought into this problem? It seems to be general,
not just specific to HTML combinators. How do you allow optional
arguments?  Does anyone have a preference to which scheme they like?

Andy Gill



Reply via email to