[Haskell-cafe] local type denotation
Brent Yorgey
byorgey at seas.upenn.edu
Wed Nov 14 13:24:28 CET 2012
Turn on the ScopedTypeVariables extension (e.g. by putting {-#
LANGUAGE ScopedTypeVariables #-} at the top of your file), and add an
explicit 'forall a.' to the type signature of f.
-Brent
On Wed, Nov 14, 2012 at 04:03:57PM +0400, Serge D. Mechveliani wrote:
> Please,
> how to correctly set an explicit type for a local value in the body of
> a polymorphic function?
>
> Example (tested under ghc-7.6.1):
>
> data D a = D1 a | D2 a (a -> a)
>
> f :: Eq a => D a -> a
> f (D1 x) = x
> f (D2 x g) = let -- y :: Eq a => a
> y = g x
> in if x == y then x else g y
>
> main = putStr $ shows (f (D2 (1 :: Int) succ)) "\n"
>
>
> This is compiled by ghc --make Main
>
> Now I need, for a certain reason, to explicitly set the type for y in
> `let', with the meaning:
> "this very `a' which is in the signature for f"
> (and I think that this type Haskell assignes to y in "y = g x").
>
> I need to declare this type in a separate line: y :: <what ever it is>.
>
> Both `y :: a' and `y :: Eq a => a' are not compiled.
>
> Please, copy the answer to mechvel at botik.ru
>
> Thanks,
>
> ------
> Sergei
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list