unsafe parsing

Kenny Lu Zhuo Ming haskellmail@yahoo.com.sg
Wed, 30 Apr 2003 15:29:04 +0800


This is a multi-part message in MIME format.

------=_NextPart_000_000F_01C30F2D.3BEC6940
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable

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:=20
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



module Test where

data Content =3D C1 Char
      | C2 String deriving Eq



class MyType a where
    parse :: Content -> (Maybe a)

data A =3D A deriving (Show,Eq)

instance MyType A where
    parse (C1 'A') =3D Just A
    parse _ =3D Nothing

data B =3D B deriving (Show,Eq)

instance MyType B where
    parse (C1 'B') =3D Just B
    parse _ =3D Nothing


data Cons x xs =3D Cons x xs deriving Show

instance (MyType x,MyType xs) =3D> MyType (Cons x xs) where
    parse (C2 (x:xs)) =3D  let maybehd =3D parse (C1 x) in
        case maybehd of=20
        Just hd ->
     let maybetl =3D parse (C2 xs) in
         case maybetl of=20
         Just tl ->
      Just ((Cons hd) tl)
         Nothing -> Nothing
        Nothing -> Nothing
    parse _ =3D Nothing


data Nil =3D Nil deriving (Show,Eq)

instance MyType Nil where=20
    parse (C2 [])  =3D Just Nil
    parse _ =3D Nothing



%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Hugs session for:
/usr/share/hugs/lib/Prelude.hs
Test.hs
Type :? for help
Test> parse (C2 "A") :: Maybe (Cons A Nil)
Just (Cons A Nil)




------=_NextPart_000_000F_01C30F2D.3BEC6940
Content-Type: text/html;
	charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable

<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.0 Transitional//EN">
<HTML><HEAD>
<META http-equiv=3DContent-Type content=3D"text/html; =
charset=3Diso-8859-1">
<META content=3D"MSHTML 6.00.2800.1141" name=3DGENERATOR>
<STYLE></STYLE>
</HEAD>
<BODY bgColor=3D#ffffff>
<DIV><FONT face=3DArial size=3D2>Hi all,</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>I am currently write a program to type =
a dynamic=20
string consist of 'A' or 'B'</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>for&nbsp;short, it works in this =
manner:=20
</FONT></DIV>
<DIV><FONT face=3DArial size=3D2>for 'A', it returns A :: A</FONT></DIV>
<DIV><FONT face=3DArial size=3D2>for 'B', it returns B :: B</FONT></DIV>
<DIV><FONT face=3DArial size=3D2>for "A", it returns Cons A Nil :: Cons =
A=20
Nil</FONT></DIV>
<DIV><FONT face=3DArial size=3D2>for "AB", it returns Cons A (Cons B =
Nil) :: Cons A=20
(Cons B Nil)</FONT></DIV>
<DIV><FONT face=3DArial size=3D2>...</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>The problem is I have to specifically =
annotate the=20
output type, which is unaffordable, because I might have arbitrary-long=20
string,</FONT></DIV>
<DIV><FONT face=3DArial size=3D2>and I have&nbsp;infinitely many =
possible singleton=20
types.</FONT></DIV>
<DIV><FONT face=3DArial size=3D2>It seems it is impossible to do it in a =
type-safe=20
way. Anyone of you have any idea to walk around that?</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>Regards,</FONT></DIV>
<DIV><FONT face=3DArial size=3D2>Kenny</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>module Test where</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>data Content =3D C1=20
Char<BR>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; | C2 String deriving =
Eq</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>class MyType a =
where<BR>&nbsp;&nbsp;&nbsp; parse ::=20
Content -&gt; (Maybe a)</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>data A =3D A deriving =
(Show,Eq)</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>instance MyType A =
where<BR>&nbsp;&nbsp;&nbsp; parse=20
(C1 'A') =3D Just A<BR>&nbsp;&nbsp;&nbsp; parse _ =3D =
Nothing</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>data B =3D B deriving =
(Show,Eq)</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV>
<DIV><FONT face=3DArial size=3D2>instance MyType B =
where<BR>&nbsp;&nbsp;&nbsp; parse=20
(C1 'B') =3D Just B<BR>&nbsp;&nbsp;&nbsp; parse _ =3D =
Nothing</FONT></DIV>
<DIV><FONT face=3DArial size=3D2></FONT>&nbsp;</DIV><FONT face=3DArial =
size=3D2>
<DIV><BR>data Cons x xs =3D Cons x xs deriving Show</DIV>
<DIV>&nbsp;</DIV>
<DIV>instance (MyType x,MyType xs) =3D&gt; MyType (Cons x xs)=20
where<BR>&nbsp;&nbsp;&nbsp; parse (C2 (x:xs)) =3D&nbsp; let maybehd =3D =
parse (C1 x)=20
in<BR>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; case maybehd of=20
<BR>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; Just hd=20
-&gt;<BR>&nbsp;&nbsp;&nbsp;&nbsp; let maybetl =3D parse (C2 xs)=20
in<BR>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; case maybetl of=20
<BR>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; Just tl=20
-&gt;<BR>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; Just ((Cons hd)=20
tl)<BR>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; Nothing -&gt;=20
Nothing<BR>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; Nothing -&gt;=20
Nothing<BR>&nbsp;&nbsp;&nbsp; parse _ =3D Nothing</DIV>
<DIV>&nbsp;</DIV>
<DIV><BR>data Nil =3D Nil deriving (Show,Eq)</DIV>
<DIV>&nbsp;</DIV>
<DIV>instance MyType Nil where <BR>&nbsp;&nbsp;&nbsp; parse (C2 =
[])&nbsp; =3D Just=20
Nil<BR>&nbsp;&nbsp;&nbsp; parse _ =3D Nothing<BR></DIV>
<DIV>&nbsp;</DIV>
<DIV>&nbsp;</DIV>
<DIV>%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%</DIV>
<DIV>Hugs session =
for:<BR>/usr/share/hugs/lib/Prelude.hs<BR>Test.hs<BR>Type :?=20
for help<BR>Test&gt; parse (C2 "A") :: Maybe (Cons A Nil)<BR>Just (Cons =
A=20
Nil)<BR></DIV>
<DIV>&nbsp;</DIV>
<DIV>&nbsp;</DIV>
<DIV>&nbsp;</DIV></FONT></BODY></HTML>

------=_NextPart_000_000F_01C30F2D.3BEC6940--