On Wed, 25 Feb 1998, Jerzy Karczmarczuk wrote:

: PS. Could somebody inform me what is the current status of
: multi-parametric classes? Concretely (for example) I would
: like to construct a generic Universal Parser
: 
:  type Uparser a c = [c] -> [(a,[c])]
: 
: which consumes any stream and produces any result. The classical
: combinators do not care about [c] being character strings, but
: with two parameters it is not possible to apply directly the magic 
: word Monad. Of course, my problem is not veeery dramatic, but
: those multiparametric classes bother me already some time. 

Well, it is actually possible to solve with Haskell 1.4 without multi
parameter type classes.

Instead of making a specific parser data type, I've implemented a general
state transformer type, which can be directly used as a parser.

it has the type

> newtype StateM s m a = SM (s -> m (a,s))
> unStateM (SM f) = f

and takes three arguments, a state type, a container monad and the result
type.

a typical Monad instantiation looks like this

> instance Monad m => Monad (StateM s m) where
>   (SM stm) >>= f = SM $ \s -> stm s >>= \(v,s') -> unStateM (f v) s'
>   return v = SM $ \s -> return (v, s)

so your Uparser would be

> type Uparser a c = StateM c [] a

I have actually implemented the Hugs Parselib using these types.
If you are interested, you can mail me for the source.

        n.

---[ www.dtek.chalmers.se/~d95mback ]--[ PGP: 0x453504F1 ]--[ UIN: 4439498 ]---


Reply via email to