Hi,

I've looked at:
http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7

but still have a problem with the attached program that fails with:

GHCi, version 7.1.20101010: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling Main             ( HasKey.hs, interpreted )

HasKey.hs:17:10:
    Couldn't match type `key' with `key1'
      because this skolem type variable would escape: `key1'
    This skolem is bound by the instance declaration
    In the instance declaration for `Ord (Keyed x)'

at the final instance for Ord.

The original code comes from
http://hackage.haskell.org/packages/archive/uni-util/2.2.0.0/doc/html/Util-VariableSet.html

Cheers Christian
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}

class Ord key => HasKey x key | x -> key where
   toKey :: x -> key

newtype Keyed x = Keyed { unKey :: x }

lift :: (HasKey x1 key1,HasKey x2 key2)
   => (key1 -> key2 -> a) -> (Keyed x1 -> Keyed x2 -> a)
lift f x1 x2 = f (toKey . unKey $ x1) (toKey . unKey $ x2)

instance HasKey x key => Eq (Keyed x) where
   (==) = lift (==)

instance HasKey x key => Ord (Keyed x)
_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to