[Haskell-beginners] Restrict type in phantom data-type

David McBride toad3k at gmail.com
Fri Sep 1 14:50:09 UTC 2017


This is maybe edging toward haskell-cafe territory, but you can
definitely do this in haskell.

{-# LANGUAGE DataKinds, KindSignatures #-}

data DayType = Sunny | Rainy

data Day (a :: DayType) = Day


sunnyDay :: Day Sunny
sunnyDay = Day

rainyDay :: Day Rainy
rainyDay = Day

-- impossibleDay :: Day ()
-- impossibleDay = Day

On Fri, Sep 1, 2017 at 10:18 AM, Baa <aquagnu at gmail.com> wrote:
> Hello, List!
>
> For example, I have specialized (right nameis phantom?) type:
>
>   data Day a = Day { ... no `a` here }
>   data Sunny
>   data Rainy
>
>   joyToday :: Day Sunny -> IO ()
>   joyToday day = ...
>
>   melancholyToday :: Day Rainy -> IO ()
>   melancholyToday day = ...
>
> And I can create (in spite of that it's phantom) some day:
>
>   let day1 = Day {...} :: Day Sunny
>   joyToday day1
>
> but no problem to create `Day Int`, `Day Char`, etc which is
> pointless actually (sure "creator"-function can be exported from the
> module only, but I'm talking about type-level solution).
>
> I know that constraints (`... =>`) on data types are redundant/removed
> from the language. And I'm not sure how it's possible to restrict that
> parameter `a` (I know that it's possible to Java/C++/Perl6 (not sure),
> some other languages but how to add such restriction in Haskell? IMHO
> type families can help but I'm not sure how it will look (Sunny, Rainy
> are "nullary" type, so...).
>
> Is it possible for Haskell too?
>
> ===
> Best regards, Paul
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


More information about the Beginners mailing list