
So here's a totally wild idea Sjoerd and I came up with. What if newtypes were unwrapped implicitly? What advantages and disadvantages would it have? In what cases would this lead to ambiguous code? Thanks, Martijn.

Isn't that the point of type-classes? Martijn van Steenbergen wrote:
So here's a totally wild idea Sjoerd and I came up with.
What if newtypes were unwrapped implicitly?
What advantages and disadvantages would it have? In what cases would this lead to ambiguous code?
Thanks,
Martijn. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Tony Morris http://tmorris.net/

Out of curiosity, why would one want a "newtype" that were unwrapped implicitly, rather than just using "type"? Personally, whenever I use a newtype it is precisely because I *want* the compiler not to implicitly turn it into something else in order to protect myself. Cheers, Greg On Dec 2, 2009, at 4:16 PM, Martijn van Steenbergen wrote:
So here's a totally wild idea Sjoerd and I came up with.
What if newtypes were unwrapped implicitly?
What advantages and disadvantages would it have? In what cases would this lead to ambiguous code?
Thanks,
Martijn. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Gregory Crosswhite
Out of curiosity, why would one want a "newtype" that were unwrapped implicitly, rather than just using "type"?
One reason might be because you only switched from 'type' to 'newtype' so that you could write more refined Arbitrary instances for your QuickCheck tests. -Greg

On Wed, Dec 2, 2009 at 6:08 PM, Greg Fitzgerald
Gregory Crosswhite
wrote: Out of curiosity, why would one want a "newtype" that were unwrapped implicitly, rather than just using "type"?
One reason might be because you only switched from 'type' to 'newtype' so that you could write more refined Arbitrary instances for your QuickCheck tests.
Maybe that is an indication that we should use a checker combinator library instead of typeclasses for automated testing. Less convenient, more adaptable. Luke

Ah, that's a really good point. It seems then that there is a use for implicitly unwrapped newtypes, but perhaps only when you never really wanted to use a newtype to begin with but had to in order to use a different instance declaration for the same type. That suggests that the feature we'd really like is a way to declare that we want a type in a context to act as if it had a different instance declaration for a given typeclass, without having to go through newtype. Cheers, Greg On Dec 2, 2009, at 5:08 PM, Greg Fitzgerald wrote:
Gregory Crosswhite
wrote: Out of curiosity, why would one want a "newtype" that were unwrapped implicitly, rather than just using "type"?
One reason might be because you only switched from 'type' to 'newtype' so that you could write more refined Arbitrary instances for your QuickCheck tests.
-Greg

That suggests that the feature we'd really like is a way to declare that we want a type in a context to act as if it had a different instance declaration for a given typeclass, without having to go through newtype.
I'd want implicit type coercion from subtypes, so that you wouldn't need an infinite hierarchy of nested typeclasses to implement the following for all integers: data One = One -- Somehow tell GHC that One is a subset of Integer (without implementing Num) oneToInteger :: One -> Integer oneToInteger One = 1 One + One == (2 :: Integer) Seems like something Agda could handle. -Greg

But it seems to me like the whole point of using "newtype" is because you *don't* want your new type to be used everywhere that the old type can be used; otherwise you would just use "type" to create an alias. The only convincing exception I have heard to this (as you helpfully explained to me) is that one might be forced to use newtype to make a piece of code use a different instance declaration for a type. In particular, I am not sure what you are getting at with your example, since one :: Integer one = 1 works just as well. Why did you want to define a new type? Cheers, Greg On Dec 2, 2009, at 6:40 PM, Greg Fitzgerald wrote:
That suggests that the feature we'd really like is a way to declare that we want a type in a context to act as if it had a different instance declaration for a given typeclass, without having to go through newtype.
I'd want implicit type coercion from subtypes, so that you wouldn't need an infinite hierarchy of nested typeclasses to implement the following for all integers:
data One = One
-- Somehow tell GHC that One is a subset of Integer (without implementing Num) oneToInteger :: One -> Integer oneToInteger One = 1
One + One == (2 :: Integer)
Seems like something Agda could handle.
-Greg

2009/12/3 Gregory Crosswhite
But it seems to me like the whole point of using "newtype" is because you *don't* want your new type to be used everywhere that the old type can be used; otherwise you would just use "type" to create an alias. The only convincing exception I have heard to this (as you helpfully explained to me) is that one might be forced to use newtype to make a piece of code use a different instance declaration for a type.
You might also be forced to use a newtype because you need to use it recursively - i.e. you need an alternative to equirecursive types. I hit this quite often when building datatype using fixpoints-of-a-functor and regularly wish for the ability to write: type Fix f = f (Fix f) Cheers, Max

Hi, Am Donnerstag, den 03.12.2009, 01:16 +0100 schrieb Martijn van Steenbergen:
So here's a totally wild idea Sjoerd and I came up with.
What if newtypes were unwrapped implicitly?
What advantages and disadvantages would it have? In what cases would this lead to ambiguous code?
not sure if this is what you are thinking at, but everytime I wrap a type Foo in a newtype MyFoo to define my own instances (or just for more expressiveness code), I wish I had a way to tell the compiler: „Please define function myfoo to be the same as foo, with all occurences of Foo in its type signature replaced by MyFoo.“ Instead I find my self writing manually code like myfoo :: (Blubb -> MyFoo) -> MyFoo -> MyFoo -> MyFoo myfoo f (MyFoo a) (MyFoo b) = MyFoo (foo (unMyFoo . f) a b) I guess TH could probably do this. Greetings, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

Hmm, as long as you provide a type signature, Haskell could do implicit wrapping as well. If I'm not mistaken, the compiler should be able to figure out what to do in this case:
myfoo :: (Blubb -> MyFoo) -> MyFoo -> MyFoo -> MyFoo myfoo = foo
Sjoerd On Dec 3, 2009, at 11:07 AM, Joachim Breitner wrote:
Hi,
Am Donnerstag, den 03.12.2009, 01:16 +0100 schrieb Martijn van Steenbergen:
So here's a totally wild idea Sjoerd and I came up with.
What if newtypes were unwrapped implicitly?
What advantages and disadvantages would it have? In what cases would this lead to ambiguous code?
not sure if this is what you are thinking at, but everytime I wrap a type Foo in a newtype MyFoo to define my own instances (or just for more expressiveness code), I wish I had a way to tell the compiler: „Please define function myfoo to be the same as foo, with all occurences of Foo in its type signature replaced by MyFoo.“
Instead I find my self writing manually code like
myfoo :: (Blubb -> MyFoo) -> MyFoo -> MyFoo -> MyFoo myfoo f (MyFoo a) (MyFoo b) = MyFoo (foo (unMyFoo . f) a b)
I guess TH could probably do this.
Greetings, Joachim
-- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher sjoerd@w3future.com

Hi, Am Donnerstag, den 03.12.2009, 11:25 +0100 schrieb Sjoerd Visscher:
Hmm, as long as you provide a type signature, Haskell could do implicit wrapping as well.
If I'm not mistaken, the compiler should be able to figure out what to do in this case:
myfoo :: (Blubb -> MyFoo) -> MyFoo -> MyFoo -> MyFoo myfoo = foo
Maybe it should, but it does not: $ cat test.hs data Foo = Foo newtype MyFoo = MyFoo { unMyFoo :: Foo } foo :: Foo -> (() -> Foo) -> Foo foo Foo f = Foo myfoo :: MyFoo -> (() -> MyFoo) -> MyFoo myfoo = foo $ runhaskell test.hs test.hs:9:8: Couldn't match expected type `MyFoo' against inferred type `Foo' In the expression: foo In the definition of `myfoo': myfoo = foo Greetings, JOachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de

Perhaps what you are looking for is a more powerful "defining" semantics? newtype MyFoo = Foo defining (Foo(..)) -- all class instances that Foo has are delegated through from MyFoo Matthew
not sure if this is what you are thinking at, but everytime I wrap a type Foo in a newtype MyFoo to define my own instances (or just for more expressiveness code), I wish I had a way to tell the compiler: „Please define function myfoo to be the same as foo, with all occurences of Foo in its type signature replaced by MyFoo.“

Hi, Am Donnerstag, den 03.12.2009, 11:13 +0000 schrieb Matthew Pocock:
Perhaps what you are looking for is a more powerful "defining" semantics?
newtype MyFoo = Foo defining (Foo(..)) -- all class instances that Foo has are delegated through from MyFoo
it goes into the right direction, but I’d also like to have this also capeable to derive single functions (giving them a new name), and not only class instances. Greetings, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de

On Thu, Dec 3, 2009 at 6:28 AM, Joachim Breitner
Hi,
Am Donnerstag, den 03.12.2009, 11:13 +0000 schrieb Matthew Pocock:
Perhaps what you are looking for is a more powerful "defining" semantics?
newtype MyFoo = Foo defining (Foo(..)) -- all class instances that Foo has are delegated through from MyFoo
it goes into the right direction, but I’d also like to have this also capeable to derive single functions (giving them a new name), and not only class instances.
Something like the restricted type synonym extension in Hugs?
http://cvs.haskell.org/Hugs/pages/users_guide/restricted-synonyms.html
--
Dave Menendez

Hi, Am Donnerstag, den 03.12.2009, 13:03 -0500 schrieb David Menendez:
On Thu, Dec 3, 2009 at 6:28 AM, Joachim Breitner
wrote: Am Donnerstag, den 03.12.2009, 11:13 +0000 schrieb Matthew Pocock:
Perhaps what you are looking for is a more powerful "defining" semantics?
newtype MyFoo = Foo defining (Foo(..)) -- all class instances that Foo has are delegated through from MyFoo
it goes into the right direction, but I’d also like to have this also capeable to derive single functions (giving them a new name), and not only class instances.
Something like the restricted type synonym extension in Hugs?
http://cvs.haskell.org/Hugs/pages/users_guide/restricted-synonyms.html
yes, this is very close to what I’d hope for. Last minor (but really minor) wish: I don’t think it would hurt to allow the use of this feature independent of the definition of the newtype: I could have a newtype Foo = Foo Int somewhere, possibly in a different module, and write something like myFoo :: Foo -> (Foo,Foo) resolving Foo myFoo a = (a,a+a) (syntax and wording very ad hoc and not thought through). But yes, I think I’d be happy to have hugs’ extension here at hand sometimes. Greetings, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de

I guess TH could probably do this.
I think this does what you wish for: http://hackage.haskell.org/packages/archive/peakachu/0.2/doc/html/Data-Newty... Example:
$(mkWithNewtypeFuncs [2] ''ZipList) withZipList2 (<*>) [(+3), (*3)] [6, 7] [9, 21] $(mkInNewtypeFuncs [2] ''ZipList) getZipList $ inZipList2 (++) (ZipList "hello ") (ZipList "world") "hello world"
in some future this won't be in this unrelated "peakachu" package, and
be incorporated into Neil M's derive.
but for now this is where you can find it.
cheers,
Yair
On Dec 3, 12:07 pm, Joachim Breitner
Hi,
Am Donnerstag, den 03.12.2009, 01:16 +0100 schrieb Martijn van Steenbergen:
So here's a totally wild idea Sjoerd and I came up with.
What if newtypes were unwrapped implicitly?
What advantages and disadvantages would it have? In what cases would this lead to ambiguous code?
not sure if this is what you are thinking at, but everytime I wrap a type Foo in a newtype MyFoo to define my own instances (or just for more expressiveness code), I wish I had a way to tell the compiler: „Please define function myfoo to be the same as foo, with all occurences of Foo in its type signature replaced by MyFoo.“
Instead I find my self writing manually code like
myfoo :: (Blubb -> MyFoo) -> MyFoo -> MyFoo -> MyFoo myfoo f (MyFoo a) (MyFoo b) = MyFoo (foo (unMyFoo . f) a b)
I guess TH could probably do this.
Greetings, Joachim
-- Joachim "nomeata" Breitner mail: m...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nome...@joachim-breitner.de |http://www.joachim-breitner.de/ Debian Developer: nome...@debian.org
signature.asc < 1KViewDownload
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, Am Donnerstag, den 03.12.2009, 10:22 -0800 schrieb yairchu@gmail.com:
I guess TH could probably do this.
I think this does what you wish for: http://hackage.haskell.org/packages/archive/peakachu/0.2/doc/html/Data-Newty...
Example:
$(mkWithNewtypeFuncs [2] ''ZipList) withZipList2 (<*>) [(+3), (*3)] [6, 7] [9, 21] $(mkInNewtypeFuncs [2] ''ZipList) getZipList $ inZipList2 (++) (ZipList "hello ") (ZipList "world") "hello world"
in some future this won't be in this unrelated "peakachu" package, and be incorporated into Neil M's derive. but for now this is where you can find it.
Nice, and close. It seems it does not handle the datatype in arbitrary positions in the type (as in Foo -> ( a -> Either Foo ())) -> (Foo, ())). But thanks for the pointer. Maybe I should give it a shot. Greetings, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de

Hi, Am Donnerstag, den 03.12.2009, 22:39 +0100 schrieb Joachim Breitner:
Nice, and close. It seems it does not handle the datatype in arbitrary positions in the type (as in Foo -> ( a -> Either Foo ())) -> (Foo, ())). But thanks for the pointer. Maybe I should give it a shot.
I started to write a module. My (incomplete!) code looks like this: ===================================================== {-# LANGUAGE PatternGuards #-} module OpenNewtype (openNewType) where import Debug.Trace import Language.Haskell.TH import Data.Monoid import qualified Data.Map as M openNewtype typeName declsQ = do info <- reify typeName decls <- declsQ tmpName1 <- newName "x" tmpName2 <- newName "x" -- Check if the given type is really a simple newtype case info of TyConI (NewtypeD _ _ _ (NormalC constr [(NotStrict,ConT realType)]) _) -> let types = getTypeMap decls in return $ map (go constr tmpName2 tmpName2 realType types) decls _ -> error $ "openNewType can only handle siple newtype defined types\nArgument was: " ++ pprint info where go constr tmpName1 tmpName2 realType types d = case d of (ValD (VarP name) _ _) -> FunD name [Clause [] (NormalB (wrap name types)) [d]] (FunD name _) -> FunD name [Clause [] (NormalB (wrap name types)) [d]] _ -> d where wrap name types | Just t <- M.lookup name types = wrapCo (VarE name) t | otherwise = (VarE name) wrapCo exp (ConT t) | t == typeName = inject exp | otherwise = exp wrapCo exp (ForallT _ _ t) = wrapCo exp t wrapCo exp (VarT _) = exp wrapCo exp (TupleT _) = exp wrapCo exp (ArrowT) = exp wrapCo exp (ListT) = exp wrapCo exp (AppT (AppT ArrowT t1) t2) = LamE [VarP tmpName1] (wrapCo (AppE exp (wrapCon (VarE tmpName1) t1)) t2) wrapCon exp (ConT t) | t == typeName = unwrap exp | otherwise = exp wrapCon exp (ForallT _ _ t) = wrapCo exp t wrapCon exp (VarT _) = exp wrapCon exp (TupleT _) = exp wrapCon exp (ArrowT) = exp wrapCon exp (ListT) = exp wrapCon exp (AppT (AppT ArrowT t1) t2) = LamE [VarP tmpName1] (wrapCon (AppE exp (wrapCo (VarE tmpName1) t1)) t2) inject :: Exp -> Exp inject e = AppE (ConE constr) e unwrap :: Exp -> Exp unwrap e = LetE [ValD (ConP constr [VarP tmpName2]) (NormalB e) []] (VarE tmpName2) getTypeMap :: [Dec] -> M.Map Name Type getTypeMap = mconcat . map go where go (SigD name t) = M.singleton name t go _ = mempty ===================================================== And the intended usage would be ===================================================== {-# LANGUAGE TemplateHaskell #-} import OpenNewtype newtype Foo = Foo Int deriving Show $(openNewtype ''Foo [d| nullFoo :: Foo nullFoo = 0 {- toFoo :: Int -> Foo toFoo = id fromFoo :: Foo -> Int fromFoo = id -} succFoo :: Foo -> Foo succFoo = succ addFoo :: Foo -> Foo -> Foo addFoo a b = a + b |] ) main = do print (succFoo (Foo 1)) ===================================================== And indeed, it works for null, succFoo, addFoo. The generated code looks like this, for example for succfoo: succFoo :: Main.Foo -> Main.Foo succFoo = \ x[a28u] -> Main.Foo (succFoo (let Main.Foo x[a28v] = x[a28u] in x[a28v])) where succFoo = GHC.Enum.succ But when I uncommented the definition of toFoo and fromfoo, I got: Demo.hs:11:9: Couldn't match expected type `Foo' against inferred type `Int' In the expression: id In the definition of `toFoo': toFoo = id In the second argument of `openNewtype', namely `[d| nullFoo :: Foo nullFoo = 0 toFoo :: Int -> Foo toFoo = id .... |]' And just now, after writing half the code, I find out that $( fun [d|...|] ) runs the type checker on the declarations before passing them to fun, which of course kills my whole approach here, as only having the declarations pass through openNewType will make them type check. Is there any way to pass declarations to a TH function so that their names are resolved, but their type is not checked (or, alternatively, type errors are ignored). If not, what would be a sane work-around? Greetings, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de

On Thu, Dec 3, 2009 at 6:00 PM, Joachim Breitner
But when I uncommented the definition of toFoo and fromfoo, I got:
Demo.hs:11:9: Couldn't match expected type `Foo' against inferred type `Int' In the expression: id In the definition of `toFoo': toFoo = id In the second argument of `openNewtype', namely `[d| nullFoo :: Foo nullFoo = 0 toFoo :: Int -> Foo toFoo = id .... |]'
And just now, after writing half the code, I find out that $( fun [d|...|] ) runs the type checker on the declarations before passing them to fun, which of course kills my whole approach here, as only having the declarations pass through openNewType will make them type check.
Is there any way to pass declarations to a TH function so that their names are resolved, but their type is not checked (or, alternatively, type errors are ignored).
If not, what would be a sane work-around?
You could switch over to using a quasi-quoter. I think there's one on hackage for parsing haskell declarations you might be able to start with: http://hackage.haskell.org/package/haskell-src-meta More on GHC quasi-quotations: http://www.haskell.org/ghc/docs/latest/html/users_guide/template-haskell.htm... Antoine

On Thu, Dec 3, 2009 at 9:10 PM, Antoine Latter
On Thu, Dec 3, 2009 at 6:00 PM, Joachim Breitner
wrote: But when I uncommented the definition of toFoo and fromfoo, I got:
Demo.hs:11:9: Couldn't match expected type `Foo' against inferred type `Int' In the expression: id In the definition of `toFoo': toFoo = id In the second argument of `openNewtype', namely `[d| nullFoo :: Foo nullFoo = 0 toFoo :: Int -> Foo toFoo = id .... |]'
And just now, after writing half the code, I find out that $( fun [d|...|] ) runs the type checker on the declarations before passing them to fun, which of course kills my whole approach here, as only having the declarations pass through openNewType will make them type check.
Is there any way to pass declarations to a TH function so that their names are resolved, but their type is not checked (or, alternatively, type errors are ignored).
If not, what would be a sane work-around?
You could switch over to using a quasi-quoter. I think there's one on hackage for parsing haskell declarations you might be able to start with:
http://hackage.haskell.org/package/haskell-src-meta
More on GHC quasi-quotations:
http://www.haskell.org/ghc/docs/latest/html/users_guide/template-haskell.htm...
So I gave it a try: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=13575 But it doesn't work, and I don't understand TH enough to figure out why. I'm guessing that the TH code can't associate the parsed type name with the passed-in type name, so we don't know to do the proper unwrapping/wrapping. Antoine

Hi, Am Freitag, den 04.12.2009, 01:00 +0100 schrieb Joachim Breitner:
And just now, after writing half the code, I find out that $( fun [d|...|] ) runs the type checker on the declarations before passing them to fun, which of course kills my whole approach here, as only having the declarations pass through openNewType will make them type check.
Is there any way to pass declarations to a TH function so that their names are resolved, but their type is not checked (or, alternatively, type errors are ignored).
If not, what would be a sane work-around?
I found one. openNewType now expects a type synonym declaration as the very first declaration. It will then replace the type synonym by the given type name in every type signature (which is simple, thanks to Data.Generics), and change the function definition to wrap and unwarp the types as needed. So the following actually works now: $(openNewtype ''Foo [d| type Foo' = Int nullFoo :: Foo' nullFoo = 0 toFoo :: Int -> Foo' toFoo = id fromFoo :: Foo' -> Int fromFoo = id succFoo :: Foo' -> Foo' succFoo = succ addFoo :: Foo' -> Foo' -> Foo' addFoo a b = a + b |] ) Given this OpenNewType module: ==================================== {-# LANGUAGE PatternGuards #-} module OpenNewtype where import Debug.Trace import Language.Haskell.TH import Data.Monoid import qualified Data.Map as M import Data.Generics.Schemes import Data.Generics.Aliases openNewtype newTypeName declsQ = do info <- reify newTypeName (taDecl:decls) <- declsQ tmpName1 <- newName "x" tmpName2 <- newName "x" -- Check if the given type is really a simple newtype typeAlias <- case taDecl of TySynD typeAlias [] concreteType -- Could check concrete Type against newtype -> return typeAlias _ -> error $ "openNewType needs a type synosym declaration as the first declaration\nFirst declaration was: " ++ pprint taDecl case info of TyConI (NewtypeD _ _ _ (NormalC constr [(NotStrict,ConT _)]) _) -> let types = getTypeMap decls in return $ map (go constr tmpName1 tmpName2 typeAlias types) decls _ -> error $ "openNewType can only handle siple newtype defined types\nArgument was: " ++ pprint info where go constr tmpName1 tmpName2 typeAlias types d = case d of (ValD (VarP name) _ _) -> FunD name [Clause [] (NormalB (wrap name types)) [d]] (FunD name _) -> FunD name [Clause [] (NormalB (wrap name types)) [d]] (SigD _ _) -> everywhere (mkT (\tn -> if tn == typeAlias then newTypeName else tn)) d _ -> d where wrap name types | Just t <- M.lookup name types = wrapCo (VarE name) t | otherwise = (VarE name) -- Short-Circuit if type to be replaced does not occur wrapCo exp t | not (doesTypeNameOccur typeAlias t) = exp wrapCo exp (ConT t) = inject exp wrapCo exp (ForallT _ _ t) = wrapCo exp t wrapCo exp (VarT _) = exp wrapCo exp (TupleT _) = exp wrapCo exp (ArrowT) = exp wrapCo exp (ListT) = exp wrapCo exp (AppT (AppT ArrowT t1) t2) = LamE [VarP tmpName1] (wrapCo (AppE exp (wrapCon (VarE tmpName1) t1)) t2) -- Short-Circuit if type to be replaced does not occur wrapCon exp t | not (doesTypeNameOccur typeAlias t) = exp wrapCon exp (ConT t) = unwrap exp wrapCon exp (ForallT _ _ t) = wrapCo exp t wrapCon exp (VarT _) = exp wrapCon exp (TupleT _) = exp wrapCon exp (ArrowT) = exp wrapCon exp (ListT) = exp wrapCon exp (AppT (AppT ArrowT t1) t2) = LamE [VarP tmpName1] (wrapCon (AppE exp (wrapCo (VarE tmpName1) t1)) t2) inject :: Exp -> Exp inject e = AppE (ConE constr) e unwrap :: Exp -> Exp unwrap e = LetE [ValD (ConP constr [VarP tmpName2]) (NormalB e) []] (VarE tmpName2) getTypeMap :: [Dec] -> M.Map Name Type getTypeMap = mconcat . map go where go (SigD name t) = M.singleton name t go _ = mempty doesTypeNameOccur tn t = gcount (mkQ False (== tn)) t > 0 ==================================== It is missing the functionality to handle occurrences of Foo' in tuples or lists, and of course it will be hard to handle occurrences of Foo' in arbitrary data types (Maybe, Data.Map, user defined data types). One could use "fmap" in these cases and hope that the data type actually is a Functor (or a Cofunctor in some cases? how to tell?), but this approach will probably never work for all cases. One could just use unsafeCoerce, after checking that Foo' and Foo really refer to the same type (one as a type synonym and one as a newtype). Would that work? It would at least break if somewhere in the modified code a type class method is called, where the instances for Foo and Int differ. Greetings, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

Hi Martijn On 3 Dec 2009, at 00:16, Martijn van Steenbergen wrote:
So here's a totally wild idea Sjoerd and I came up with.
What if newtypes were unwrapped implicitly?
Subtyping.
What advantages and disadvantages would it have?
The typechecker being psychic; the fact that it isn't. It's very easy to add forms of subtyping and make a mess of type and instance inference.
In what cases would this lead to ambiguous code?
If f :: x -> ZipList y we get traverse f :: t x -> [t y] but it is not clear whether to attach the unpacking to f or to the result, and that will determine the idiom in which the traversal occurs. And that's before you start mixing the sugar of newtypes with the fertiliser of GADTs... But even if it's dangerous to unpack newtypes silently, it's rather nice to do it systematically, via a type class. Here are old posts of mine which mention this and then show off a bit. http://www.mail-archive.com/haskell-cafe@haskell.org/msg37213.html http://www.haskell.org/pipermail/libraries/2008-January/008917.html These days, how about class Newtype n where type Unpack n pack :: Unpack n -> n unpack :: n -> Unpack n and related machinery? Cheers Conor

On Thu, Dec 3, 2009 at 5:34 AM, Conor McBride wrote:
http://www.haskell.org/pipermail/libraries/2008-January/008917.html
On Tue, Jan 15, 2008 at 3:31 PM, Conor McBride wrote:
Haskell's classes are the best damn rhythm section in the industry: you hum it, they play it.
On Fri, Dec 10, 2004 at 2:21 AM, Conor McBride wrote:
If you're willing to make the types distinguish the idioms you're using, as in choice-lists and vector-lists, then a lot of routine operations wither to a huddle of combinators sitting under a type signature which actually does most of the work. Instance inference is like having a great rhythm section: you hum it, they play it.
Very eloquent Conor. Can we get this guy quoted in HWN? I think he's earned it. :-) On Thu, Dec 3, 2009 at 5:34 AM, Conor McBride wrote:
class Newtype n where type Unpack n pack :: Unpack n -> n unpack :: n -> Unpack n
Nice. Would the code below be a good way to deal with subtyping? It'd be convenient to have some way to go from a 64-bit Double to a 32-bit Float and be informed when a Double can't be represented precisely by a Float, but to have the option to move forward with the minor loss of precision. class Subset n where type Superset n demote :: Superset n -> Either n n promote :: n -> Superset n squeeze :: Subset n => Superset n -> n squeeze = either id id . demote In action: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=13554#a13554 Thanks, Greg

On Wed, Dec 2, 2009 at 7:16 PM, Martijn van Steenbergen
So here's a totally wild idea Sjoerd and I came up with.
What if newtypes were unwrapped implicitly?
From my perspective, the primary advantage to a feature like this is
As several have suggested, this creates ambiguity.
But it might be handy to have a way to declare a scope in which the
newtype is transparent. E.g.,
newtype N = N T
f :: T -> T -> T
f = ...
open N in
-- in this block, N is treated as a synonym for T
g :: N -> N -> N
g = f
This is similar to the restricted type synonyms feature in Hugs, and I
think it's straightforward to encode in GHC's System FC.
that it avoids the need to convert [N] to [T], which under the current
system effectively requires mapping an identity function over the
entire list.
But that also exposes the danger of this idea, where GADTs and type
families are involved.
data G where
A :: G N
B :: G T
a :: G N -> N
a ~A = N -- should never fail, because A is the only (non-bottom)
value of type G N.
Now, what stops me from writing something like this?
open N in
...
a B
...
(See the discussion at
http://hackage.haskell.org/trac/ghc/ticket/1496 for how this problem
crops up with generalized newtype deriving.)
--
Dave Menendez
participants (13)
-
Antoine Latter
-
Conor McBride
-
David Menendez
-
Greg Fitzgerald
-
Gregory Crosswhite
-
Joachim Breitner
-
Luke Palmer
-
Martijn van Steenbergen
-
Matthew Pocock
-
Max Bolingbroke
-
Sjoerd Visscher
-
Tony Morris
-
yairchu@gmail.com