[Haskell-beginners] How to avoid repeating a type restriction from a data constructor
Daniel Fischer
daniel.is.fischer at googlemail.com
Wed Apr 24 16:08:23 CEST 2013
On Wednesday 24 April 2013, 13:25:01, gs wrote:
> Daniel Fischer <daniel.is.fischer <at> googlemail.com> writes:
> > I meant example code using a GADT for Source, and not DatatypeContexts;
> > and
> > some function where you still need the context.
>
> OK, here are some truncated instances/functions:
>
> data Source v a where
> Source :: Variable v => {bindings :: v [Binding a] ,var :: v a} -> Source
> v a
>
> instance Variable v => Variable (Source v) where
> newVar a = do bindings <- newVar []
> v <- newVar a
> return $ Source bindings v
>
> instance Variable v => Bindable (Source v) where
> bind (Source bindings var) extract target apply =
> do let binding = Binding extract target apply
> --update the new binding
> a <- readVar var
Removing the `Variable v` context from instance declarations is at least
tricky. I don't think you can do it at all here. For the context to become
available, you need to pattern-match, but in `newVar`, the `Source` appears
only as the result. Therefore you need the `Variable v` context to be able to
write
v <- newVar a
Consequently, you can't have an
instance Variable (Source v) where ...
without context, and since `Variable b` is a superclass constraint on
`Bindable b`, you need something that guarantees that `Source x` (resp.
`BindingList x`) has a `Variable` instance.
>
> data BindingList v a where
> BindingList :: Variable v => {source :: Source v a, list :: v [v a],pos
>
> :: v Int} -> BindingList v a
>
> fromBindingList :: Variable v => BindingList v a -> IO [a]
> fromBindingList b = do update b
> readVar (list b) >>= mapM readVar
You're not pattern-matching on the constructor. I wrote that you have to do
that to make the context available:
> > The `Variable v` context becomes available by pattern-matching on the
constructor `Source` (but not by using the field names to deconstruct a value
of type `Source v a`!).
Pattern-matching,
fromBindingList :: BindingList v a -> IO [a]
fromBindingList b@(BindingList s l p)
= do update b
readVar l >>= mapM readVar
removes the need to mention the `Variable v` context.
More information about the Beginners
mailing list