[Haskell-cafe] Typeclass problem

Bjorn Bringert d00bring at dtek.chalmers.se
Thu Jul 29 14:02:56 EDT 2004


Mark T.B. Carroll wrote:
> I have a little programme that doesn't compile:
> 
> 	module Example where
> 
> 	class (Show c, Ord c, Bounded c) => MyClass c
> 
> 	showThings :: MyClass c => c -> (String, String)
> 
> 	showThings x =
> 	    let foo = maxBound :: c
> 	     in (show x, show foo)
> 
> If I change that second-to-last line to,
> 
> 	    let foo = max x maxBound
> 
> then it compiles. However, it's clearly silly to use "max" just to make
> the type of the maxBound be the same type as the x. (I'm assuming that the
> Ord and the Bounded instances of the type are sensibly consistent.)
> 
> What should I be writing if I want foo to be the maxBound applied to the
> type that x is?

You could use asTypeOf from the Prelude:

  let foo = maxBound `asTypeOf` x

-- asTypeOf is a type-restricted version of const.  It is usually used
-- as an infix operator, and its typing forces its first argument
-- (which is usually overloaded) to have the same type as the second.

asTypeOf         :: a -> a -> a
asTypeOf         =  const


Also, Hugs and GHC both support an extension which lets you put type 
annotations in patterns:

showThings (x::c) =
	    let foo = maxBound :: c
	     in (show x, show foo)

/Bjorn


More information about the Haskell-Cafe mailing list