
Hi Huong, attached you find a small program for parsing values of various (data) types. It uses a generalized algebraic data type for representing types and a universal data type for representing values. The parser itself is rather simple-minded: it builds on Haskell's "ReadS" type. I don't know whether this is what you are after, but it was fun writing. There are many opportunities for improvement: one could use a decent combinator library for parsing; a type of dynamic values instead of a universal type etc. Here are some example calls: 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\"]" [(ValList [ValString "hello world"],"")] Note that "parseAny" even parses heterogenous lists. Cheers, Ralf ---
{-# OPTIONS -fglasgow-exts #-}
data Type :: * -> * where Char :: Type Char Int :: Type Int List :: Type a -> Type [a] Value :: Type Value
string :: Type String string = List Char
parse :: Type t -> ReadS t parse (Char) = reads parse (Int) = reads parse (List Char) = reads parse (List a) = parseList (parse (a)) parse (Value) = parseAny
data Value = ValChar Char | ValInt Int | ValString String | ValList [Value] deriving (Show)
parseAny = ValChar <$> parse Char <+> ValInt <$> parse Int <+> ValString <$> parse string <+> ValList <$> parse (List Value)
Helper functions.
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