[Haskell-beginners] Concrete instance of abstract class
Brent Yorgey
byorgey at seas.upenn.edu
Wed Jun 5 21:14:27 CEST 2013
On Thu, Jun 06, 2013 at 12:08:46AM +0800, Adrian May 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
This does not really make sense (or at least it is not very useful),
because it says that a Turtlish thing *must* be able to use *any* type
s as its state. But presumably, for each Turtlish thing you have some
*particular* type s in mind. I would do this using an associated
type, like so:
class Turtlish t where
type TState t :: *
pic :: t -> Dia
state :: t -> TState t
move :: TState t -> t -> t
(>>>),(+++) :: t -> t -> t
x >>> y = x +++ move (state x) y
This says that to every type t which is an instance of Turtlish, there
is an associated type called (TState t).
-Brent
>
> 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.
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
More information about the Beginners
mailing list