Automatically infer Newtype instance

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

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

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?
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
No, it is not what I want. With it I would have to enumerate every type
down. so for A_n
newtype A0 = A0 Int
...
newtype A_n = A_n A_{n-1}
I would need list all n instances. In more general say, I want
following:
class Foo a b where
foo :: a -> b
--- Yes, UndecidableInstances. Yes, ambitious types.
--- Take any b, yes unsafe, trust me, it will be okay.
instance (Foo a b, Foo b c) => Foo a c where
foo = foo . foo
--
Best regards, Dmitry Bogatov

Try using scoped type variables, and explicitly declare the types for pack
and unpack at the call site:
instance (Newtype a b, Newtype b c) => Newtype a c where
pack = (pack :: b -> c)
. (pack :: a -> b)
Did I get those types right? They look free to me.
On Tue, Apr 8, 2014 at 10:05 AM, 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

On Wed, Apr 9, 2014 at 11:05 AM, Alexander Solla
Try using scoped type variables, and explicitly declare the types for pack and unpack at the call site:
instance (Newtype a b, Newtype b c) => Newtype a c where pack = (pack :: b -> c) . (pack :: a -> b)
Did I get those types right? They look free to me.
Actually, I'm not sure if that will work. How will GHC know which b to choose for the pair a and c, unless there are functional dependencies on a and c?

* Alexander Solla
On Wed, Apr 9, 2014 at 11:05 AM, Alexander Solla
wrote: Try using scoped type variables, and explicitly declare the types for pack and unpack at the call site:
instance (Newtype a b, Newtype b c) => Newtype a c where pack = (pack :: b -> c) . (pack :: a -> b)
Did I get those types right? They look free to me.
Actually, I'm not sure if that will work. How will GHC know which b to choose for the pair a and c, unless there are functional dependencies on a and c?
In fact, in case of Newtype there is fundep:
class Newtype n o | n -> o where ...
so I should have c -> a. Unfortunatelly, somewhy it do not work.
But also I am interested in even more unsafe case, when there is no
fundep.
--
Best regards, Dmitry Bogatov

On Wed, Apr 9, 2014 at 2:06 PM, Alexander Solla
instance (Newtype a b, Newtype b c) => Newtype a c where pack = (pack :: b -> c) . (pack :: a -> b)
Did I get those types right? They look free to me.
Actually, I'm not sure if that will work. How will GHC know which b to choose for the pair a and c, unless there are functional dependencies on a and c?
Hi Alex, If there was no fundep on Newtype, that 'b' could also be inferred when the 'a' is actually Int, and we have an instance: instance (b ~ Key) => Newtype Int b You tend to need many type annotations when you have types that look like they are ambiguous but turn out to be unambiguous because of your particular instances: https://ghc.haskell.org/trac/ghc/ticket/8477 Regards, Adam
participants (4)
-
adam vogt
-
Alexander Solla
-
Carter Schonwald
-
Dmitry Bogatov