Parsec and type level numerals

Hello all. I've got a puzzling Parsec problem. Perhaps the collective wisdom of haskell-cafe can point me in the right direction. I want to be able to parse a string of digits to a type level numeral as described in the Number parameterized typeshttp://okmij.org/ftp/papers/number-parameterized-types.pdfpaper. After fiddling with the problem for a while, I'm not convinced it's possible- it seems as though one would need to know the type of the result before parsing, but then we wouldn't need to parse in the first place. :) My first (simplified) approximation is as follows:
data Zero = Zero data Succ a = Succ a
class Card t instance Card Zero instance (Card a) => Card (Succ a)
parseP :: (Card a) => Parser a parseP = do { char '1' ; rest <- parseP ; return $ Succ rest } <|> return Zero
I'd like for this to parse, for example, "111" into Succ Succ Succ Zero. Of course this doesn't work because parseP is ill-typed, but I'm not sure how to fix it. It seems that what I'm asking for is a function whose type is forall a. (Card a) => String -> a, which is problematic. Has anyone tried this before? I'm new to using Parsec and to parsing in general, so I apologize if this is a silly question. (Parsec is very impressive, by the way.) Thanks- Nathan Bloomfield University of Arkansas, Fayetteville

2008/12/13 Nathan Bloomfield
I want to be able to parse a string of digits to a type level numeral as described in the Number parameterized types paper.
Hi, I'm at UA too (bsl04). Here's a quick try. Sorry if I'm not getting what you're doing. import Text.Parsec import Text.Parsec.String data PeanoNumber = Zero | Succ PeanoNumber deriving Show parseP :: Parser PeanoNumber parseP = do char '1' rest <- parseP return $ Succ rest <|> return Zero test = parseTest parseP "111"

You're almost there, but you have correctly determined the problem;
you need to know the type of the parse result in order to parse.
However, it is possible to hide the type from the parser; try writing
this function instead:
{-# LANGUAGE ExistentialQuantification #-}
data AnyCard = forall t. Card t => AnyCard t
parseP :: Parser AnyCard
Now the type-level numeral is hidden in the "AnyCard" existential
type. In order to use it, you need to be able to use operations that
work on any instance of Card, which means the class/instance
declarations you have so far aren't that useful. Emulating dependent
types using existentials in Haskell is never pretty!
Another option is to use a GADT to hold the type:
{-# LANGUAGE GADTs, ExistentialQuantification #-}
data GADTNum t where
GZero :: GADTNum Zero
GSucc :: GADTNum a -> GADTNum (Succ a)
data AnyCard = forall t. AnyCard (GADTNum t)
Now, after the parse, you can use the structure of the GADT to
determine things about the existential type:
isTwo :: AnyCard -> Maybe (Succ (Succ Zero))
isTwo (AnyCard (GSucc (GSucc GZero))) = Succ (Succ Zero)
isTwo _ = Nothing
-- ryan
2008/12/13 Nathan Bloomfield
Hello all. I've got a puzzling Parsec problem. Perhaps the collective wisdom of haskell-cafe can point me in the right direction.
I want to be able to parse a string of digits to a type level numeral as described in the Number parameterized types paper. After fiddling with the problem for a while, I'm not convinced it's possible- it seems as though one would need to know the type of the result before parsing, but then we wouldn't need to parse in the first place. :) My first (simplified) approximation is as follows:
data Zero = Zero data Succ a = Succ a
class Card t instance Card Zero instance (Card a) => Card (Succ a)
parseP :: (Card a) => Parser a parseP = do { char '1' ; rest <- parseP ; return $ Succ rest } <|> return Zero
I'd like for this to parse, for example, "111" into Succ Succ Succ Zero. Of course this doesn't work because parseP is ill-typed, but I'm not sure how to fix it. It seems that what I'm asking for is a function whose type is forall a. (Card a) => String -> a, which is problematic.
Has anyone tried this before? I'm new to using Parsec and to parsing in general, so I apologize if this is a silly question. (Parsec is very impressive, by the way.)
Thanks-
Nathan Bloomfield University of Arkansas, Fayetteville
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2008/12/13 Nathan Bloomfield
I want to be able to parse a string of digits to a type level numeral as described in the Number parameterized types paper. After fiddling with the problem for a while, I'm not convinced it's possible- it seems as though one would need to know the type of the result before parsing, but then we wouldn't need to parse in the first place. :)
This can be done with existential types. I think Oleg Kiselyov has an
example somewhere of a parser that determines the type of its output
from its input, but here's the basic idea:
data SomeCard = forall a. (Card a) => SomeCard a
Now you can define parseP :: Parser SomeCard
Unfortunately, all you know about the value inside the SomeCard is
that it's a member of the class Card, which may not be very helpful.
Depending on how general you want to be, you can bundle more
operations with SomeCard, or you can return a GADT that reflects the
type-level natural at the value level.
--
Dave Menendez

On Sun, Dec 14, 2008 at 6:54 AM, David Menendez
2008/12/13 Nathan Bloomfield
: I want to be able to parse a string of digits to a type level numeral as described in the Number parameterized types paper. After fiddling with the problem for a while, I'm not convinced it's possible- it seems as though one would need to know the type of the result before parsing, but then we wouldn't need to parse in the first place. :)
This can be done with existential types. I think Oleg Kiselyov has an example somewhere of a parser that determines the type of its output from its input, but here's the basic idea:
data SomeCard = forall a. (Card a) => SomeCard a
Now you can define parseP :: Parser SomeCard
Unfortunately, all you know about the value inside the SomeCard is that it's a member of the class Card, which may not be very helpful. Depending on how general you want to be, you can bundle more operations with SomeCard, or you can return a GADT that reflects the type-level natural at the value level.
-- Dave Menendez
http://www.eyrie.org/~zednenem/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Depending on what you actually want to do, you may be looking for Oleg Kiselyov's reifyIntegral function, which he defines in the paper "Functional Pearl: Implicit Configurations -- or Type Classes Reflect the Value of Types" (at http://www.cs.rutgers.edu/~ccshan/prepose/prepose.pdf ). It has type something like reifyIntegral :: forall a. Int -> (forall n. Numeral n => n -> a) -> a encoding n's existential type with continuation passing style. Cheers, Reiner
participants (5)
-
brian
-
David Menendez
-
Nathan Bloomfield
-
Reiner Pope
-
Ryan Ingram