[Haskell-cafe] How to derive instance for type without exported constructor?

kyra kyrab at mail.ru
Fri Sep 4 11:46:00 EDT 2009


Miguel Mitrofanov wrote:
> Well, normally - you can't (unless there is some equivalent to the 
> constructor exported).
> 
> But there is a trick. You can use generic classes:
> 
> {-# OPTIONS_GHC -fglasgow-exts -XGenerics -package lang #-}
> import Generics
> class Binary' a where
>   put' :: a -> Put
>   get' :: Get a
>   put' {| Unit |} Unit = return ()
>   get' {| Unit |} = return Unit
>   put' {| a :+: b |} (Inl x) = putWord8 0 >> put' x
>   put' {| a :+: b |} (Inr y) = putWord8 1 >> put' y
>   get' {| a :+: b |} =
>     do w <- getWord8
>        case w of
>          0 -> liftM Left get'
>          _ -> liftM Right get'
>   put' {| a :*: b |} (x :*: y) = put' x >> put' y
>   get' {| a :*: b |} =
>     do x <- get'
>        y <- get'
>        return $ x :*: y
> instance Binary' Int32 where
>   put' = put
>   get' = get
> instance Binary' StdGen
> instance Binary StdGen where
>   put = put'
>   get = get'
> 

Isn't it to define an isomorphic type and unsafeCoerce to it pretty much 
equivalent?

At least the following simplest example works just fine:

module Main where

import Unsafe.Coerce

class Test a where
   test :: a -> Int

data Foo = Foo Int Int

data Bar = Bar Int Int

instance Test Bar where test (Bar a b) = a + b

instance Test Foo where test foo = test (unsafeCoerce foo :: Bar)

main :: IO ()
main = print $ test (Foo 123 345)


Cheers,
Kyra



More information about the Haskell-Cafe mailing list