Type signature inside an instance declaration

Thomas Schilling nominolo at googlemail.com
Tue Dec 16 09:22:15 EST 2008


{-# LANGUAGE ScopedTypeVariables #-}

2008/12/16 Neil Mitchell <ndmitchell at gmail.com>:
> Hi
>
>> You want to use `asTypeOf`, with a lazy pattern to name a value of type 'a'.
>>
>>    pr xs = "[" ++ pr (undefined `asTypeOf` x) ++ "]"
>>            where (x:_) = xs
>
> I prefer:
>
> pr xs = "[" ++ pr (undefined `asTypeOf` head x) ++ "]"
>
> Or even more simply:
>
> pr xs = "[" ++ pr (head x) ++ "]"
>
> I do believe there is some GHC extension that can be turned on to
> refer to variables like you did, but its not standard Haskell.
>
> Thanks
>
> Neil
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>



-- 
Push the envelope.  Watch it bend.


More information about the Glasgow-haskell-users mailing list