[Haskell-beginners] Concrete instance of abstract class

Adrian May adrian.alexander.may at gmail.com
Wed Jun 5 18:17:49 CEST 2013


BTW, I also tried adding:

class Turstateish s where
  pos :: s -> R2
  ang :: s -> CircleFrac

and guarding the instance declaration with it, but that doesn't work cos
I'd have to mention s in the instance declaration, and then the kinds would
go out of sync again.

Adrian.



On 6 June 2013 00:08, Adrian May <adrian.alexander.may at gmail.com> wrote:

> Hi folks,
>
> I just wrote this:
>
> import Diagrams.Prelude
> import Diagrams.Backend.Cairo
>
> type Dia = Diagram Cairo R2
>
> class Turtlish t where
>   pic :: t s -> Dia
>   state :: t s -> s
>   move :: s -> t s -> t s
>   (>>>),(+++) :: t s -> t s -> t s
>   x >>> y = x +++ move (state x) y
>
> The idea is that s is a turtle state, t s contains such a state along
> with a growing diagram, and >>> superimposes the diagrams after shuffling
> the right hand t s around according to the s I extract from the left hand
> t s.
>
> But I have different turtles planned. I want a regular turtle, a Sankey
> turtle which also has a width, and we could imagine sub-turtles that only
> had the angle or only the position. But in all cases, I think the above
> class describes how I want to compose diagrams together. I already tried it
> with monads but I'm now thinking that I want something like the above *
> instead* of a monad.
>
> So how do I use it to make a regular turtle? Maybe something like:
>
> data TurtState = TurtState P2 CircleFrac
> data TurtWorld s = TurtWorld Dia s
>
> I know exactly what s is above but otherwise the kinds don't match below.
>
> instance Turtlish TurtWorld where
>   pic  (TurtWorld d _) = d
>   state (TurtWorld _ s) = s
>   (TurtWorld d1 _) +++ (TurtWorld d2 s2) =
>         TurtWorld (d1 `atop` d2) s2
>   move (pp,aa) (TurtWorld d (p,a)) = TurtWorld
>     (d # rotate aa # translate pp)
>     ( (p # rotate aa + pp) , (a+aa) )
>
> Naturally, it barfs over move saying:
>
>     Couldn't match type `s' with `(R2, t0)'
>       `s' is a rigid type variable bound by
>           the type signature for move :: s -> TurtWorld s -> TurtWorld s
>           at turtle.hs:20:3
>     In the pattern: (pp, aa)
>     In an equation for `move':
>         move (pp, aa) (TurtWorld d (p, a))
>           = TurtWorld
>               (d # rotate aa # translate pp) ((p # rotate aa + pp), (a +
> aa))
>     In the instance declaration for `Turtlish TurtWorld'
>
> because it hasn't a clue what (pp,aa) is and wants s totally generic
> anyway.
>
> But what am I supposed to do instead? Isn't it an everyday thing to use a
> generic pattern with a specific type?
>
> TIA,
> Adrian.
>
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130606/38e54d2f/attachment.htm>


More information about the Beginners mailing list