On Nov 5, 2007 2:37 PM, C.M.Brown <[EMAIL PROTECTED]> wrote:
> Hi,
>
> I was given a quandary this evening, suppose I have the following code:
>
> module Test1 where
>
> import qualified Data.Map as Map
>
> testFunction :: Ord a => Map.Map a b -> Map.Map a b -> a -> (Maybe b,
> Maybe b)
> testFunction m0 m1 k = (lookup0 k, lookup1 k)
>                         where
>                           lookup0 x  = Map.lookup x m0
>
>                           lookup1 x  = Map.lookup x m1
>
> This compiles and type checks fine. However, the only way I could add type
> signatures to lookup0 and lookup1 was to do something along the lines
> of this:
>
> testFunction :: Ord a => Map.Map a b -> Map.Map a b -> a -> (Maybe b,
> Maybe b)
> testFunction m0 m1 k = (lookup0 k m0, lookup1 k m1)
>                         where
>                           lookup0 :: (Monad m, Ord a) => a -> Map.Map a b
> -> m b
>                           lookup0 x m0 = Map.lookup x m0
>
>                           lookup1 :: (Monad m, Ord a) => a -> Map.Map a b
> -> m b
>                           lookup1 x m1 = Map.lookup x m1
>
> Is there a way to give lookup0 and lookup1 explicit type signatures
> without passing in m0 and m1 as parameters? (So their definitions are the
> same as in the first example) If ghc can infer the type, surely it must
> be possible?

Yes, using a ghc extension of scoped type variables.  In the signature
of testFunction, if you explicitly quantify all your variables with
forall, then they are visible in the where clause (and elsewhere in
the function).

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

Reply via email to