
I'm starting to tidy it up:
class Turtlish t where
type Context t :: *
type Content t :: *
construct :: Content t -> Context t -> t
destruct :: t -> (Content t, Context t)
combine :: Content t -> Content t -> Content t
contemp :: Context t -> Context t -> Context t
conform :: Context t -> t -> t
present :: t -> Dia
content :: t -> Content t
content = fst.destruct
context :: t -> Context t
context = snd.destruct
(>>>),(+++) :: t -> t -> t
x +++ y = construct (content x `combine` content y) (context x
`contemp` context y)
x >>> y = x +++ conform (context x) y
but I hit this:
turtle.hs:23:32:
Could not deduce (Content t ~ Content t0)
from the context (Turtlish t)
bound by the class declaration for `Turtlish'
at turtle.hs:(9,1)-(24,47)
NB: `Content' is a type function, and may not be injective
In the return type of a call of `content'
In the first argument of `combine', namely `content x'
In the first argument of `construct', namely
`(content x `combine` content y)'
turtle.hs:23:64:
Could not deduce (Context t ~ Context t1)
from the context (Turtlish t)
bound by the class declaration for `Turtlish'
at turtle.hs:(9,1)-(24,47)
NB: `Context' is a type function, and may not be injective
In the return type of a call of `context'
In the first argument of `contemp', namely `context x'
In the second argument of `construct', namely
`(context x `contemp` context y)'
What does this mean, and how do I fix it?
TIA,
Adrian.
On 6 June 2013 11:28, Adrian May
Hi Brent,
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
Bingo. Just what I needed. But is this a Haskellish thing to do or am I showing my C++ background by even wanting something like this? Anyway, for the sake of any future googlers, I needed {-# LANGUAGE TypeFamilies #-} and completed the instance with:
instance Turtlish TurtWorld where type TState TurtWorld = TurtState ...
Thanks, Adrian.