unsafe parsing

oleg@pobox.com oleg@pobox.com
Sun, 4 May 2003 18:03:53 -0700 (PDT)


The following code works. I must admit though that I don't understand
the problem. What is the expected result?

Note that bmap is actually a type transformer, and 'funny' introduces
a constraint via a run-time witness.


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'

data BTERM = forall u. (XTERM u) => BTERM u
xtmake 'A' = BTERM A
xtmake 'B' = BTERM B

instance Show BTERM where
    show (BTERM u) = show $ xtval u
    
class XSEQ u where
    xsval:: u -> String
    isnil:: u -> Bool
    car::   u -> BTERM
    cdr::   u -> BSEQ
    
instance XSEQ Nil where
    xsval _ = []
    isnil = const True
    car = undefined
    cdr = undefined
    
instance (XTERM v, XSEQ w) => XSEQ (Cons v w) where
        xsval _ = (xtval (undefined::v)):(xsval (undefined::w))
	isnil = const False
        car _ = BTERM (undefined::v)
	cdr _ = BSEQ (undefined::w)

data BSEQ = forall u. (XSEQ u) => BSEQ u

instance Show BSEQ where
    show (BSEQ u) = show $ xsval u

bcons (BTERM u) (BSEQ t) = BSEQ $ Cons u t

xsmake [] = BSEQ Nil
xsmake (x:xs) = bcons (xtmake x) $ xsmake xs

bcar (BSEQ u) = car u
bcdr (BSEQ u) = cdr u

bmap f (BSEQ u) | isnil u = BSEQ Nil
bmap f seq = bcons (f $ bcar seq) $ bmap f (bcdr seq)


class FunnyMap u v | u -> v where
    funnymap:: u -> v
    
instance FunnyMap A B where
    funnymap _ = (undefined::B)

funny (BTERM u) = case xtval u of
                    'A' -> BTERM $ funnymap (undefined::A)
--                    'B' -> BTERM $ funnymap (undefined::B)

*Main> bmap funny $ xsmake "AAA"
"BBB"