[Haskell-cafe] local type denotation

MigMit miguelimo38 at yandex.ru
Wed Nov 14 13:24:22 CET 2012


{-# LANGUAGE ScopedTypeVariables #-}

Отправлено с iPhone

14.11.2012, в 16:03, "Serge D. Mechveliani" <mechvel at botik.ru> написал(а):

> 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