[Haskell-cafe] Re: Local functional dependencies: solving show . read and XML generation problems

Niklas Broberg niklas.broberg at gmail.com
Wed Aug 16 18:32:51 EDT 2006


Hi Oleg,

Thanks a lot for your reply. I see now where my attempt went wrong and
why it couldn't work in the first place, the instances will indeed
overlap. I'm not completely satisfied with your solution though, but
seeing how you did it has lead me to the solution I want. Details
below. :-)

] Fortunately, there is a solution that does not involve proxies or
] type annotations. We use a `syntactic hint' to tell the typechecker
] which intermediate type we want. To be more precise, we assert local
] functional dependencies. Thus we can write:
]
]      p c = build "p" [embed c]
]
]      test1 :: XML
]      test1 = p [[p [[p "foo"]]]]
]
] Our syntactic crutch is the list notation: [[x]]. We could have used a
] single pair of brackets, but we'd like to avoid overlapping
] instances (as is done in the following self-contained code).

While I appreciate the ingenuity of the solution, unfortunately I
cannot use it. First of all I don't want to require my users to write
double brackets everywhere, it makes the code a lot uglier IMO.
Another problem is that in my real library (as opposed to the
simplified example I gave here) I allow the embedding of lists, which
means that the [[x]] is not safe from overlap as it is in your
example. But I still see the general pattern here, the point is just
to get something that won't clash with other instances. I could define

  data X a = X a

  instance (TypeCast a XML) => Embed (X a) XML where
    embed (X a) = typeCast a

and write

  test1 = p (X $ p (X $ p "foo"))

Not quite so pretty, even worse than with the [[ ]] syntax.

However, I have an ace up my sleeve, that allows me to get exactly
what I want using your trick. Let's start the .lhs file first:
> {-# OPTIONS_GHC -fglasgow-exts #-}
> {-# OPTIONS_GHC -fallow-overlapping-instances #-}
> {-# OPTIONS_GHC -fallow-undecidable-instances #-}
> module HSP where
>
> import Control.Monad.State
> import Control.Monad.Writer
> import TypeCast -- putting your six lines in a different module

Now, the thing I haven't told you in my simplified version is that all
the XML generation I have in mind takes place in monadic code. In
other words, all instances of Build will be monadic. My whole point of
wanting more than one instance is that I want to use one monad, with
an XML representation, in server-side code and another in client-side
code, as worked on by Joel Björnson.

Since everything is monadic, I can define what it means to be an
XML-generating monad in terms of a monad transformer:

> newtype XMLGen m a = XMLGen (m a)
>   deriving (Monad, Functor, MonadIO)

and define the Build and Embed classes as

> class Build m xml child | m -> xml child where
>  build :: String -> [child] -> XMLGen m xml
>
> class Embed a child where
>  embed :: a -> child

Now for the server-side stuff:

> data XML = CDATA String | Element String [XML]
>  deriving Show
>
> newtype HSPState = HSPState Int -- just to have something
> type HSP' = StateT HSPState IO
> type HSP = XMLGen HSP'

Note that by including XMLGen we define HSP to be an XML-generation
monad. Now we can declare our instances.

First we can generate XML values in the HSP monad (we use HSP [XML] as
the child type to enable embedding of lists):

> instance GenXML HSP' XML (HSP [XML]) where
>  genElement s chs = do
>  	xmls <- fmap concat $ sequence chs
>  	return (Element s xmls)

Second we do the TypeCast trick, with XMLGen as the marker type:

> instance TypeCast (m x) (HSP' XML) =>
>         Embed (XMLGen m x) (HSP [XML]) where
>   embed (XMLGen x) = XMLGen $ fmap return $ typeCast x

And now we can safely declare other instances that will not clash with
the above because of XMLGen, e.g.:

> instance Embed String (HSP [XML]) where
>  embed s = return [CDATA s]
>
> instance Embed a (HSP [XML]) => Embed [a] (HSP [XML]) where
>  embed = fmap concat . mapM embed -- (why is there no concatMapM??)

This last instance is why I cannot use lists as disambiguation, and
also why I need overlapping instances. Now for some testing functions:

> p c = build "p" [embed c]

> test0 :: HSP XML
> test0 = p "foo"

> test1 :: HSP XML
> test1 = p (p "foo")

> test2 :: HSP XML
> test2 = p [p "foo", p "bar"]

All of these now work just fine. We could end here, but just to show
that it works we do the same stuff all over again for the clientside
stuff (mostly dummy code, the clientside stuff doesn't work like this
at all, this is just for show):

> data ElementNode = ElementNode String [ElementNode] | TextNode String
>  deriving Show
>
> type HJScript' = WriterT [String] (State Int)
> type HJScript = XMLGen HJScript'
>
> instance Build HJScript' ElementNode (HJScript ElementNode) where
>  build s chs = do
>  	xs <- sequence chs
>  	return $ ElementNode s xs
>
> instance TypeCast (m x) (HJScript' ElementNode) =>
>     Embed (XMLGen m x) (HJScript ElementNode) where
>  embed (XMLGen x) = XMLGen $ typeCast x
>
> instance Embed String (HJScript ElementNode) where
>  embed s = return $ TextNode s

Testing the new stuff, using the same p as above:

> test3 :: HJScript ElementNode
> test3 = p "foo"
>
> test4 :: HJScript ElementNode
> test4 = p (p "foo")

And these also work just as expected! :-)

Thanks a lot for teaching my the zen of TypeCast, it works like a
charm once you learn to use it properly. Really cool stuff! :-)

/Niklas


More information about the Haskell-Cafe mailing list