[Haskell-cafe] Generic parser without GADTs

oleg at pobox.com oleg at pobox.com
Sun Oct 16 20:50:27 EDT 2005


Also inspired by Ralf Hinze's post, I thought of removing GADTs from
that code. The result is Haskell98! code, which works well in
Hugs. The code seems to be a bit simpler too. Like the original code,
the function 'parseAny' correctly discriminates between the list of
characters (i.e., strings) and the list of other things.

{-- Haskell98! --}

class Type a where
  parse :: ReadS a

newtype Str = Str{unStr :: String}

instance Type Char   where parse = reads
instance Type Int    where parse = reads
instance Type Str    where parse = Str <$> reads
instance Type a => Type [a] where parse = parseList parse
instance Type Value where parse = parseAny

data Value
    =  ValChar    Char
    |  ValInt     Int
    |  ValString  String
    |  ValList    [Value]
       deriving (Show)

parseAny
    =   ValChar   <$> parse
    <+> ValInt    <$> parse
    <+> ValString <$> (unStr <$> parse)
    <+> ValList   <$> parse


-- The following is Ralf Hinze's code verbatim
parseList parsea
    =  readParen False (\ s -> [ xs | ("[", t) <- lex s, xs <- parsel t ])
  where parsel  s  =   [ ([],     t) | ("]", t) <- lex s ]
		   ++  [ (x : xs, u) | (x,   t) <- parsea s,
			               (xs,  u) <- parsel' t ]
	parsel' s  =   [ ([],     t) | ("]", t) <- lex s ]
		   ++  [ (x : xs, v) | (",", t) <- lex s,
			               (x,   u) <- parsea t,
			               (xs,  v) <- parsel' u]

infix  8  <$>
infixr 6  <+>
(f <$> p) s  =  [ (f a, t) | (a, t) <- p s ]
(p <+> q) s  =  p s ++ q s



Tests:

  > hugs /tmp/h.hs
  Haskell 98 mode: Restart with command line option -98 to enable extensions

  Main> parseAny "4711"
  [(ValInt 4711,"")]
  Main> parseAny "\"4711\""
  [(ValString "4711","")]
  Main> parseAny "[4711, 0]"
  [(ValList [ValInt 4711,ValInt 0],"")]
  Main> parseAny "[4711, 'a']"
  [(ValList [ValInt 4711,ValChar 'a'],"")]
  Main> parseAny "[\"hello world\"] x"
  [(ValList [ValString "hello world"]," x")]


More information about the Haskell-Cafe mailing list