[Haskell-cafe] Funny type signature question

Michael Snoyman michael at snoyman.com
Thu Apr 2 14:54:16 EDT 2009


On Thu, Apr 2, 2009 at 9:51 PM, Felipe Lessa <felipe.lessa at gmail.com> wrote:

> On Thu, Apr 02, 2009 at 08:18:27PM +0200, Peter Verswyvelen wrote:
> > The type inferer seems to struggle to find the type of minBound and
> > maxBound, and GHC asks to use a type annotation.
> > To only way I see how to add a type annotation here is to use a GHC
> > extension:
> >
> > {-# LANGUAGE ScopedTypeVariables #-}
>
> Just use 'asTypeOf'. It is defined as
>
> > asTypeOf :: a -> a -> a
> > asTypeOf = const
>
> so that @asTypeOf x y == x@ but both types are constrained to be
> equal.  The above function would become
>
> > randomEnum :: (Enum a, Bounded a, RandomGen g) => Rand g a
> > randomEnum = do
> >     let min = minBound; max = maxBound
> >     randVal <- getRandomR (fromEnum min, fromEnum max)
> >     return $ toEnum randVal `asTypeOf` min `asTypeOf` max
>
> Note that I use the fact that 'return' is constrained to the type
> variable 'a' we want to constrain its argument, and the
> 'asTypeOf' constrains everything to be of the same type.
>
> HTH,
>
> --
> Felipe.
>

Interesting alternative. However, I think the ScopedTypeVariables looks a
little bit cleaner. I'll keep the asTypeOf in mind for the future though.

Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090402/600089df/attachment.htm


More information about the Haskell-Cafe mailing list