
you should checkout genealizednewtype deriving :)
https://ghc.haskell.org/trac/haskell-prime/wiki/NewtypeDeriving
GHC has had it for quite some time
also the Coerce Machinery in 7.8 GHC provides a stronger version of your
NewType style class
On Tue, Apr 8, 2014 at 1:05 PM, Dmitry Bogatov
Hello! I think, that Newtype instances are transitive, and there is only one sane definiton is (pack . pack). But in example below I have to use UndecidableInstances and they seems to loop somewhere (Context reduction stack overflow; size = 132).
To my understanding, Ghc tries to prove, that exists only one type b, and somewhy fail at it(It is unclear, why), but is it any way to say to it that I take responsibility, that ANY b would be nice?
I know about TH, but interested in more elegant solution.
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-}
import Control.Newtype
newtype A1 = A1 Int deriving (Eq, Show) newtype A2 = A2 A1 deriving (Eq, Show)
instance Newtype A1 Int where pack = A1 unpack (A1 a) = a
instance Newtype A2 A1 where pack = A2 unpack (A2 a) = a
-- Here comes UndecidableInstances instance (Newtype a b, Newtype b c) => Newtype a c where pack = pack . pack unpack = unpack . unpack
main = let foo :: A2 foo = pack "46" in print foo
-- Best regards, Dmitry Bogatov
, Free Software supporter, esperantisto and netiquette guardian. git://kaction.name/rc-files.git GPG: 54B7F00D _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe