[Haskell-cafe] Re: Wikipedia on first-class object

Ryan Ingram ryani.spam at gmail.com
Mon Dec 31 05:56:42 EST 2007


On 12/30/07, Cristian Baboi <cristi at ot.onrc.ro> wrote:
>
> Thank you.
>
> data Something = This | S Something
>
> ppp :: Something -> String
>
> ppp This = ""
> ppp (S x) = 'S':(ppp x)
>
>
> How can I prevent one to pass  'let x = S x in x' to ppp ?


 {-# LANGUAGE GADTs, EmptyDataDecls #-}
data Z
data S a

data Something a where
    This :: Something Z
    S :: Something a -> Something (S a)

ppp :: Something a -> String
ppp This =  ""
ppp (S x) = 'S' : ppp x
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20071231/622a808d/attachment-0001.htm


More information about the Haskell-Cafe mailing list