[Haskell-cafe] local type denotation

Erik Hesselink hesselink at gmail.com
Wed Nov 14 13:25:48 CET 2012


You need to enable ScopedTypeVariables, and add a forall to introduce the
type variable at the top level. The local variable will then be the *same*
'a' instead of a fresh one:

  {-# LANGUAGE ScopedTypeVariables #-}

  data D a = D1 a | D2 a (a -> a)

  f :: forall a. 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"


On Wed, Nov 14, 2012 at 1:03 PM, Serge D. Mechveliani <mechvel at botik.ru>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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121114/c6140cb2/attachment.htm>


More information about the Haskell-Cafe mailing list