unsafe parsing

Derek Elkins ddarius@hotpop.com
Sat, 3 May 2003 01:36:55 -0400


On Sat, 3 May 2003 12:14:04 +0800
"Kenny Lu Zhuo Ming" <haskellmail@yahoo.com.sg> wrote:

> Kenny
> ----- Original Message -----
> From: "Derek Elkins" <ddarius@hotpop.com>
> To: "Kenny Lu Zhuo Ming" <haskellmail@yahoo.com.sg>
> Cc: <haskell@haskell.org>
> Sent: Wednesday, April 30, 2003 9:47 PM
> Subject: Re: unsafe parsing
> 
> 
> > On Wed, 30 Apr 2003 15:29:04 +0800
> > "Kenny Lu Zhuo Ming" <haskellmail@yahoo.com.sg> wrote:
> 
> > > Hi all,
> > >
> > > I am currently write a program to type a dynamic string consist of
> > > 'A' or 'B'
> > >
> > > for short, it works in this manner:
> > > for 'A', it returns A :: A
> > > for 'B', it returns B :: B
> > > for "A", it returns Cons A Nil :: Cons A Nil
> > > for "AB", it returns Cons A (Cons B Nil) :: Cons A (Cons B Nil)
> > > ...
> > >
> > > The problem is I have to specifically annotate the output type,
> > > which is unaffordable, because I might have arbitrary-long string,
> > > and I have infinitely many possible singleton types. It seems it
> > > is impossible to do it in a type-safe way. Anyone of you have any
> > > idea to walk around that?
> > >
> > >
> > >
> > > Regards,
> > > Kenny
> 
> > Is there any reason [Either A B] couldn't be used?  Otherwise, you
> > may want to look at the thread "polymorphic stanamically typed
> > balanced trees" on this list (or haskell-cafe), and/or
> > SimulatingDependentTypes on the Haskell Wiki (it's linked from
> > haskell.org). SimulatingDependentTypes also has a link to the
> > aforementioned thread.
>
> Well, it seems that it doesn't quite help here. 

This isn't very surprising.  For one reason or another, I didn't quite
get what you meant earlier.

> Because the resulting
> existentially qualifed typess
> are always in form of variable, there is no way I can apply a function
> which requires static type,
> for example: data A = A deriving Show
> data B = B deriving Show
> data Cons x xs = Cons x xs deriving Show
> data Nil = Nil deriving Show
> class XTERM u where xtval:: u -> Char
> instance XTERM A where xtval _ = 'A'
> instance XTERM B where xtval _ = 'B'
> 
> class XSEQ u where xsval:: u -> String
> instance XSEQ Nil where xsval _ = []
> instance (XTERM v, XSEQ w) => XSEQ (Cons v w) where
>         xsval _ = (xtval (undefined::v)):(xsval (undefined::w))
> 
> data BTERM = forall u. (XTERM u) => BTERM u
> xtmake 'A' = BTERM A
> xtmake 'B' = BTERM B
> xtmake _ = error ""
> data BSEQ = forall u. (XSEQ u) => BSEQ u
> xsmake [] = BSEQ Nil
> xsmake (x:xs) = case (xtmake x) of
>                         (BTERM (t::tt)) -> case (xsmake xs) of
>                                 (BSEQ (s::ss)) -> BSEQ ((Cons t
>                                 s)::(Cons tt
> ss))
> 
> class Funny a b | a->b where
>     funny :: a->b
> instance (Funny rest rest') => Funny (Cons A rest) (Cons B rest')
> where
>     funny (Cons A rest) = Cons B (funny rest)
> instance Funny Nil Nil where
>     funny Nil = Nil
> 
> this funny function will turn a sequence of A in the a sequence of B.
> when I apply it to the (xsmake "AA"), ghc complains
> 
> *ABSEQ> case (xsmake "AA") of (BSEQ u::t) -> funny u
> :1: Could not deduce (Funny u b) from the context (XSEQ u)
> Probable fix: Add (Funny u b) to the existential context of a data
> constructor arising from use of `funny' at
> :1 In a case alternative: funny u

> It seems at somepoint I need a unsafe type casting.

What will that give you?  You won't statically know where to put them,
what do you expect the rest the program to do with the coerced object,
what are you going to coerce to what?

The only thing you could do with a type cast is cast something to some
uniform object, then later cast it back and use it.  However, obviously,
you'll need some flag or tag to decide what to cast back to.  One
way or another you'll need a runtime check.  However, this describes 
exactly how union (sum) types work, Either being the simplest
non-trivial example. Just expand it to however many different types
you need.  If that doesn't seem flexible or modular enough, then there
are also extensible sums or Dynamics.  There is no need for a coerce
function.