Hi!

The `constraints` package provides ways to manipulate objects of kind `Constraint`. I need the same kind of manipulation, except that I need to work with objects of kind `* -> Constraint`. I.e. I need parameterized constraints that can be applied to different types.

BTW, is there a standard term for things of kind `* -> Constraint`?

I have a type family

  type family Constr (f :: * -> *) :: * -> Constraint

which returns a parameterized constraint with the property that any value of type `f a` fulfills the constraint `Constr f a`. Since the constraint can be stronger than needed, I need something similar to `:-` from `constraints`, except it should operate on parameterized constraints.

I have implemented the stuff I need (see below), but my question is if it's possible to do this with the `constraints` package directly (e.g. using `Forall`). I'm afraid I can't see how.

Here is what I've come up with so far:

  -- Instead of (c1,c2)
  class    (c1 a, c2 a) => (c1 :/\: c2) a
  instance (c1 a, c2 a) => (c1 :/\: c2) a

  -- Instead of (:-)
  type sub :< sup = forall a . Dict (sup a) -> Dict (sub a)

  -- Instead of weaken1
  weak1 :: c1 :< (c1 :/\: c2)
  weak1 Dict = Dict

  weak2 :: c2 :< (c1 :/\: c2)
  weak2 Dict = Dict

Thanks!

--
/ Emil


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to