[Haskell-cafe] A question about data declaration
Erik Hesselink
hesselink at gmail.com
Thu Mar 21 13:58:17 CET 2013
You could use a GADT:
{-# LANGUAGE GADTs #-}
data T a where
C1 :: Int -> T Int
C2 :: Char -> T Char
C3 :: T Char -> T Char
This will allow you to put a C3 in a C3. If you want to prevent that,
just invent some other index, something like:
{-# LANGUAGE GADTs, EmptyDataDecls #-}
data Yes
data No
data T a where
C1 :: Int -> T No
C2 :: Char -> T Yes
C3 :: T Yes -> T No
Not sure if this is a *better* way though. Your initial solution is
also ok, I guess.
Regards,
Erik
On Thu, Mar 21, 2013 at 1:48 PM, C K Kashyap <ckkashyap at gmail.com> wrote:
> Hi,
>
> I have a situation where I need to define a data type T such that
>
> data T = C1 Int | C2 Char | C3 T
>
> However, I want to enforce a constraint that C3 only allows (C2 Char) and
> not (C1 Int). That is
>
> x = C3 (C1 10) -- should not compile - but my above definition will let it
> compile
>
>
> I was thinking of this -
>
> data C1 = C1 Int
> data C2 = C2 Char
> data T = TC1 C1 | TC1 C2 | TC3 C2
>
> Is there a better way to do it?
>
> Regards,
> Kashyap
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list