<div dir="ltr"><div>Thanks Andras and Daniil for pointing out the singletons package.</div><div><br></div>I will need to look into this in more detail to fully understand what is going on. Seems I'm jumping into the deep end with this. Type families have move up in my reading list!</div>
<div class="gmail_extra"><br><br><div class="gmail_quote">On Wed, Jan 15, 2014 at 9:55 PM, Andras Slemmer <span dir="ltr"><<a href="mailto:0slemi0@gmail.com" target="_blank">0slemi0@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
<div dir="ltr"><div class="im"><div>> I have been looking at DataKinds and GADTs, but I can't quite figure out if they actually help me here at all.<br></div></div><div>You are on the right track. With DataKinds and GADTs you can create an index type for PenShape:<div class="im">
<br>
<br>data Shape = Circle | Rectangle | Arbitrary<br><br></div>data PenShape s where<br>    PenCircle :: Float -> PenShape Circle<br>    PenRectangle :: Float -> Float -> PenShape Rectangle<br>    ArbitraryPen :: PenShape Arbitrary<br>

<br></div><div>You can use this index 's' to restrict PenShape to a particular constructor, or none at all:<br><br>data Stroke where<br>    Spot :: Point -> PenShape s -> Stroke -- any shape allowed<br>    Arc :: Point -> Point -> Point -> PenShape Circle -> Stroke -- only circle<br>

<br></div><div>In the Spot case the type variable 's' will be existentially hidden, meaning any type can go there.<br><br></div><div>The tricky part comes when you want to have a notion of "or" in the case of Line. We basically need decidable type equality for this. Let's assume we have a way of deciding whether two lifted Shape types are equal and we get back a lifted Bool. Now we can write a type level "or" function:<br>

<br>type family Or (a :: Bool) (b :: Bool) :: Bool<br>type instance Or False False = False<br>type instance Or True b = True<br>type instance Or a True = True<br><br></div><div>Now the Line case in the GADT would look something like this:<br>

<br>    Line :: Or (s :== Circle) (s :== Rectangle) ~ True =>       -- circle or rectangle<br>            Point -> Point -> PenShape s -> Stroke<br><br></div><div>where :== is our type equality predicate. You can write this by hand if you'd like but it's pretty tedious and really should be inferred by the compiler or some automated process. And indeed the 'singletons' library does just this (and more), all you need to do is wrap your Shape definition in some th:<br>

<br>$(singletons [d|data Shape = Circle | Rectangle | Arbitrary deriving (Eq)|])<br><br></div><div>And voila you have a nice type safe datastructure:)<br><br></div><div>A full module can be found here: <a href="http://lpaste.net/98527" target="_blank">http://lpaste.net/98527</a><br>

</div></div><div class="HOEnZb"><div class="h5"><div class="gmail_extra"><br><br><div class="gmail_quote">On 13 January 2014 16:25, Daniil Frumin <span dir="ltr"><<a href="mailto:difrumin@gmail.com" target="_blank">difrumin@gmail.com</a>></span> wrote:<br>

<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">I devised the following (unarguably verbose) solution using the<br>
singletons [1] library<br>
<br>
{-# LANGUAGE DataKinds, TypeFamilies, MultiParamTypeClasses #-}<br>
{-# LANGUAGE TemplateHaskell, GADTs, FlexibleContexts #-}<br>
module Image where<br>
import Data.Singletons<br>
<br>
type Point = (Float,Float)<br>
<br>
$(singletons [d|<br>
 data Shape' = Circle' | Rectangle' | Arbitrary'<br>
            deriving (Eq)<br>
 data Stroke' = Line' | Arc' | Spot'<br>
            deriving (Eq)<br>
 |])<br>
<br>
<br>
data PenShape shape where<br>
    Circle :: SingI Circle' => Float -> PenShape Circle'<br>
    Rectangle :: SingI Rectangle' => Float -> Float -> PenShape Rectangle'<br>
    ArbitraryPen :: PenShape Arbitrary'<br>
<br>
class AllowedStroke (a::Stroke') (b::Shape') where<br>
<br>
instance AllowedStroke Line' Circle'<br>
instance AllowedStroke Line' Rectangle'<br>
instance AllowedStroke Arc' Circle'<br>
instance AllowedStroke Spot' Circle'<br>
instance AllowedStroke Spot' Rectangle'<br>
instance AllowedStroke Spot' Arbitrary'<br>
<br>
data Stroke where<br>
    Line :: AllowedStroke Line' a<br>
         => Point -> Point -> PenShape a -> Stroke<br>
    Arc  :: AllowedStroke Arc' a<br>
         => Point -> Point -> Point -> PenShape a -> Stroke<br>
    Spot :: AllowedStroke Spot' a<br>
         => Point -> PenShape a -> Stroke<br>
<br>
{-<br>
h> :t Line (1,1) (1,1) (Circle 3)<br>
Line (1,1) (1,1) (Circle 3) :: Stroke<br>
h> :t Line (1,1) (1,1) (Rectangle 3 3)<br>
Line (1,1) (1,1) (Rectangle 3 3) :: Stroke<br>
h> :t Line (1,1) (1,1) ArbitraryPen<br>
<br>
<interactive>:1:1:<br>
    No instance for (AllowedStroke 'Line' 'Arbitrary')<br>
      arising from a use of `Line'<br>
    Possible fix:<br>
      add an instance declaration for (AllowedStroke 'Line' 'Arbitrary')<br>
    In the expression: Line (1, 1) (1, 1) ArbitraryPen<br>
-}<br>
<br>
--- unfortunately this still gives non-exhaustive pattern match<br>
    --- warning :(<br>
showStroke :: Stroke -> String<br>
showStroke (Line _ _ (Circle _)) = "Line + Circle"<br>
showStroke (Line _ _ (Rectangle _ _)) = "Line + Rect"<br>
showStroke (Arc _ _ _ (Circle _)) = "Arc"<br>
showStroke (Spot _  _) = "Spot"<br>
<br>
The shortcomings of this approach are the following:<br>
  - verbosity and repetition (eg: Shape' and Shape)<br>
  - still gives pattern matching warning ( I suspect that's because<br>
typeclasses are open and there is really no way of determining whether<br>
something is an 'AllowedStroke' or not)<br>
<br>
Feel free to improve the code and notify the list :)<br>
<br>
[1] <a href="http://hackage.haskell.org/package/singletons" target="_blank">http://hackage.haskell.org/package/singletons</a><br>
<div><div><br>
On Mon, Jan 13, 2014 at 7:38 AM, Luke Clifton <<a href="mailto:ltclifton@gmail.com" target="_blank">ltclifton@gmail.com</a>> wrote:<br>
> Hi,<br>
><br>
> I'm quite new to Haskell, and have been loving exploring it. I've always<br>
> been a huge fan of languages that let me catch errors at compile time,<br>
> finding dynamic languages like Python a nightmare to work in. I'm finding<br>
> with Haskell I can take this compile time checking even further than most<br>
> static languages and it has gotten me rather excited. So I was wondering if<br>
> there is a Haskell way of solving my problem.<br>
><br>
> I'm trying to represent an image made up of a list of strokes. Strokes are<br>
> either lines, arcs or spots, and can be made using different pen shapes.<br>
><br>
> data Image = Image [Stroke]<br>
><br>
> data Stroke = Line Point Point PenShape<br>
>     | Arc Point Point Point PenShape<br>
>     | Spot Point PenShape<br>
><br>
> data PenShape = Circle Float<br>
>     | Rectangle Float Float<br>
>     | ArbitraryPen -- Stuff (not relevant)<br>
><br>
> And this is all great and works.<br>
><br>
> But now I have a problem. I want to extend this such that Arc strokes are<br>
> only allowed to have the Circle pen shape, and Lines are only allowed to<br>
> have the Rectangle or Circle pen shapes.<br>
><br>
> What is the best way of enforcing this in the type system.<br>
><br>
> I could make more Strokes like LineCircle, LineRectangle, Arc, PointCircle,<br>
> PointRectangle, PointArbitrary and get rid of the PenShape type altogether.<br>
> But this doesn't really feel good to me (and seems like the amount of work I<br>
> have to do is bigger than it needs to be, especially if I added more basic<br>
> pen shapes).<br>
><br>
> I thought about making the different PenShapes different types, using<br>
> typeclasses and making Stroke an algebraic data type, but then my strokes<br>
> would be of different types, and I wouldn't be able to have a list of<br>
> strokes.<br>
><br>
> I have been looking at DataKinds and GADTs, but I can't quite figure out if<br>
> they actually help me here at all.<br>
><br>
> I'm sure there is a way to do this, I'm just not googling properly.<br>
><br>
> What I want to write is...<br>
><br>
> data Image = Image [Stroke]<br>
><br>
> data Stroke = Line Point Point (Circle or Rectangle)<br>
>     | Arc Point Point Point Circle<br>
>     | Spot Point PenShape<br>
><br>
> data PenShape = Circle Float<br>
>     | Rectangle Float Float<br>
>     | ArbitraryPen -- Stuff (not relevant)<br>
><br>
> Regards,<br>
><br>
> Luke<br>
><br>
</div></div><div>> _______________________________________________<br>
> Haskell-Cafe mailing list<br>
> <a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
> <a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
><br>
<br>
<br>
<br>
</div><span><font color="#888888">--<br>
Sincerely yours,<br>
-- Daniil<br>
</font></span><div><div>_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</div></div></blockquote></div><br></div>
</div></div></blockquote></div><br></div>