warn-identities from newtype deriving

2017-03-14 Thread Evan Laforge
I just noticed that if you derive Real for a Ratio.Rational newtype, you get a warning: {-# LANGUAGE GeneralizedNewtypeDeriving #-} import qualified Data.Ratio as Ratio newtype X = X Ratio.Rational deriving (Eq, Ord, Num, Real) You get a warning: : Warning: Call of toRational :: Rational

Re: Deriving clauses for EmptyDataDecls [was: request for reviews for my first patch -- ticket 7401]

2013-08-14 Thread Edward A Kmett
, but I would actually favor not implementing any change here, because the workaround -- using standalone deriving -- is so easy and doesn't seem to have any real drawbacks (e.g. performance). Hmmm, I'm sort of ambivalent at this point. Looking at the user manual[1], the relevant point

Deriving clauses for EmptyDataDecls [was: request for reviews for my first patch -- ticket 7401]

2013-08-13 Thread Austin Seipp
, because the workaround -- using standalone deriving -- is so easy and doesn't seem to have any real drawbacks (e.g. performance). Hmmm, I'm sort of ambivalent at this point. Looking at the user manual[1], the relevant point for -XStandaloneDeriving is that Unlike a deriving declaration

Re: Type error when deriving Generic for an associated data type

2012-07-13 Thread Bas van Dijk
On 12 July 2012 12:33, Andres Löh and...@well-typed.com wrote: Your example compiles for me with HEAD (but fails with 7.4.1 and 7.4.2, yes). I've not tested if it also works. Great, I will wait for a new release then. Bas ___ Glasgow-haskell-users

Type error when deriving Generic for an associated data type

2012-07-12 Thread Bas van Dijk
Hi, I'm hitting on an issue when deriving Generic for an associated data type: {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DeriveGeneric #-} import GHC.Generics class Foo a where data T a :: * instance Foo Int where data T Int = Bla deriving Generic Couldn't match type `Rep (T Int

Re: Type error when deriving Generic for an associated data type

2012-07-12 Thread Andres Löh
Hi Bas. I'm hitting on an issue when deriving Generic for an associated data type: [...] Your example compiles for me with HEAD (but fails with 7.4.1 and 7.4.2, yes). I've not tested if it also works. Cheers, Andres -- Andres Löh, Haskell Consultant Well-Typed LLP, http://www.well

Re: Type error when deriving Generic for an associated data type

2012-07-12 Thread José Pedro Magalhães
Hi Bas, On Thu, Jul 12, 2012 at 11:27 AM, Bas van Dijk v.dijk@gmail.com wrote: Hi, I'm hitting on an issue when deriving Generic for an associated data type: ... The GHC trac seems to be down. Is this a known issue? Yes, and it's supposed to be fixed in HEAD. Can you try

Error when deriving Typeable for associated type

2012-01-30 Thread Bas van Dijk
Hello, Given the following program: --- {-# LANGUAGE DeriveDataTypeable, TypeFamilies #-} import Data.Typeable class C a where data T a :: * data MyType1 = MyType1 deriving Typeable data MyType2 = MyType2 deriving Typeable instance

Deriving Typeable -- possible improvement

2011-07-14 Thread Simon Peyton-Jones
| iterIO uses mkTyCon for the simple reason that ((Typeable t, Typeable | m) = Iter t m) is Typeable1 and there is no automatic way of deriving | Typeable1. This email is triggered by a thread on Haskell Cafe about changes to the Typeable class http://www.mail-archive.com/haskell-cafe

Newtype deriving mixing up types

2010-12-16 Thread Emil Axelsson
) -- Prints Main.BOOL (correct) test1 and test2 give different results, even though showType shouldn't be able to tell them apart. It seems that the Typeable context packed with the Lit constructor is wrong in test2. I had to use two extra classes and newtype deriving to trigger this behavior

RE: standalone binary deriving

2010-05-05 Thread Simon Peyton-Jones
-users@haskell.org | Subject: standalone binary deriving | | compiling the following fragment in ghci | | {-# LANGUAGE StandaloneDeriving #-} | | import Data.Binary (Binary) | | newtype Pair a b = Pair (a,b) | deriving instance (Binary a, Binary b) = Binary (Pair a b) | | results in the following

standalone binary deriving

2010-05-04 Thread Ben
compiling the following fragment in ghci {-# LANGUAGE StandaloneDeriving #-} import Data.Binary (Binary) newtype Pair a b = Pair (a,b) deriving instance (Binary a, Binary b) = Binary (Pair a b) results in the following message: Prelude :load /Users/catbee/Documents/dev/haskell/savestream

RE: Deriving regression or bad code?

2010-04-12 Thread Simon Peyton-Jones
of an exotic case because of the higher-kindedness so I don't think it'll bite too man people There's a good workaround: use standalone deriving. You | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf

Re: Deriving regression or bad code?

2010-04-12 Thread Ron Alford
I was getting a similar error with standalone deriving (already attached to that bug), but I didn't try it through-out. I'll let you know how it goes. -Ron On Mon, Apr 12, 2010 at 6:01 AM, Simon Peyton-Jones simo...@microsoft.com wrote: It's really a bug. I've fixed it in my tree, but I'm

RE: Deriving regression or bad code?

2010-04-12 Thread Simon Peyton-Jones
The standalone deriving decl you need is the one for (Data (a :+: b)), not for Expr Simon | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf Of Ron Alford | Sent: 12 April 2010 11:09 | To: Simon Peyton

Re: Deriving regression or bad code?

2010-04-10 Thread Ron Alford
Just for fun, I tried it on 6.12.1.20100330 with the same result. Does anyone have a workaround? Otherwise I need to revert to 6.10. -Ron On Thu, Apr 8, 2010 at 10:35 AM, Ron Alford ronw...@volus.net wrote: At Igloo's suggestion, it's now a ticket:

Re: Deriving regression or bad code?

2010-04-08 Thread Ron Alford
At Igloo's suggestion, it's now a ticket: http://hackage.haskell.org/trac/ghc/ticket/3965 -Ron On Thu, Apr 8, 2010 at 1:39 AM, Ron Alford ronw...@volus.net wrote: I've attached the simplest example of my code that used to compile in GHC 6.10 now gives the error in GHC 6.12.1: ...

Deriving regression or bad code?

2010-04-07 Thread Ron Alford
I've attached the simplest example of my code that used to compile in GHC 6.10 now gives the error in GHC 6.12.1: baddata.hs:33:14: No instances for (Data Const, Data Var) arising from the 'deriving' clause of a data type declaration at baddata.hs:33:14-17 Possible

nasty things possible with generalized newtype deriving

2010-03-09 Thread Wolfgang Jeltsch
Hello guys, are you following this Haskell Cafe thread: http://www.mail-archive.com/haskell-c...@haskell.org/msg72300.html Seems that you can do ugly things with GHC’s current implementation of generalized newtype deriving. For example, you can easily construct sets with corrupted

RE: [Haskell] deriving Show for GADT?

2009-04-14 Thread Simon Peyton-Jones
...@haskell.org] On Behalf Of | Norman Ramsey | Sent: 14 April 2009 05:28 | To: hask...@haskell.org | Subject: [Haskell] deriving Show for GADT? | | I've got a fairly large GADT for which I wished to use |deriving (Show) | but I got a mysterious error message: | | Exp.hs:13:11: | Can't make

Re: [Haskell] deriving Show for GADT?

2009-04-14 Thread Lennart Augustsson
If it's easy I think just generating the code and let the type checker report any problems would be a great thing for standalone deriving. -- Lennart On Tue, Apr 14, 2009 at 10:10 AM, Simon Peyton-Jones simo...@microsoft.com wrote: Yes, indeed, see http://hackage.haskell.org/trac/ghc/ticket

Re: Bug in deriving Data Typeable?

2009-03-13 Thread José Pedro Magalhães
Hello, On Thu, Mar 12, 2009 at 17:02, Bernd Brassel b...@informatik.uni-kiel.dewrote: José Pedro Magalhães wrote: Hi Bernd, I guess this might be the same issue reported some time ago ( http://thread.gmane.org/gmane.comp.lang.haskell.generics/53/focus=54): the derived instances of

Bug in deriving Data Typeable?

2009-03-12 Thread Bernd Brassel
yields () But when I define my own version of Maybe and derive the Data/Typeable instances data MyMaybe a = MyJust a | MyNothing deriving (Data,Typeable) the corresponding test useExt1' :: Data a = a - () useExt1' = undefined `ext1Q` (\ (MyJust _) - ()) testExt1' :: () testExt1' = useExt1

Re: Bug in deriving Data Typeable?

2009-03-12 Thread José Pedro Magalhães
a = a - () useExt1 = undefined `ext1Q` (\ (Just _) - ()) testExt1 :: () testExt1 = useExt1 (Just ()) As I expected, testExt1 yields () But when I define my own version of Maybe and derive the Data/Typeable instances data MyMaybe a = MyJust a | MyNothing deriving (Data,Typeable

Re: Bug in deriving Data Typeable?

2009-03-12 Thread Bernd Brassel
José Pedro Magalhães wrote: Hi Bernd, I guess this might be the same issue reported some time ago ( http://thread.gmane.org/gmane.comp.lang.haskell.generics/53/focus=54): the derived instances of Data do not define dataCast1. If you define your own instance of Data for MyMaybe and add the

Deriving Functor

2008-12-06 Thread Twan van Laarhoven
Functor T: - First to determine whether the deriving should be allowed at all (checkSideConditions) - Then to determine the constraints needed (mk_data_eqn) - Finally to make the body of the instance (gen_Functor_binds) This seems a bit redundant, and currently the code

automatically deriving Functor Re[2]: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Bulat Ziganshin
Hello Neil, Thursday, June 5, 2008, 8:54:51 PM, you wrote: PS Why isn't Functor derivable? Derive can do it: http://www.cs.york.ac.uk/~ndm/derive I believe that Twan (the author of Functor deriving in Derive) is trying to get this suggested for Haskell' as a proper deriving. dear GHC

Re: Expected behavior of deriving Ord?

2008-03-31 Thread Christian Maeder
Christian Maeder wrote: Conal Elliott wrote: The type argument I ran into trouble with represents a value as a list of increasing lower bounds, ending in the exact value. min produces lower bounds from lower bounds and so is immediately productive before even knowing which argument is the

Re: Expected behavior of deriving Ord?

2008-03-31 Thread Conal Elliott
The issue is more than just efficiency. It's vital that these improving values get evaluated as little as possible. In my use for functional reactivity, they represent the times of future event occurrences. Your (=)-via-min idea might work in some cases, though useful pointer equality can be

Re: Expected behavior of deriving Ord?

2008-03-22 Thread Christian Maeder
Conal Elliott wrote: The type argument I ran into trouble with represents a value as a list of increasing lower bounds, ending in the exact value. min produces lower bounds from lower bounds and so is immediately productive before even knowing which argument is the lesser one. Is this only

Re: Expected behavior of deriving Ord?

2008-03-20 Thread Christian Maeder
Conal Elliott wrote: I have an algebraic data type (not newtype) that derives Ord: data AddBounds a = MinBound | NoBound a | MaxBound deriving (Eq, Ord, Read, Show) The class Ord is not suited for partial orders. If you write your own Ord instances anyway, I'd suggest

Re: Expected behavior of deriving Ord?

2008-03-20 Thread Christian Maeder
Conal Elliott wrote: AddBounds makes total orders from total orders. It just adds new least and greatest elements. The problem with the derived instance is that it doesn't exploit the potential laziness of min on 'a'. Because of their types, min it can produce partial info from partial

Re: Expected behavior of deriving Ord?

2008-03-20 Thread Conal Elliott
Oh -- partial partial. Thanks. I was pretty puzzled there. The type argument I ran into trouble with represents a value as a list of increasing lower bounds, ending in the exact value. min produces lower bounds from lower bounds and so is immediately productive before even knowing which

Expected behavior of deriving Ord?

2008-03-19 Thread Conal Elliott
I have an algebraic data type (not newtype) that derives Ord: data AddBounds a = MinBound | NoBound a | MaxBound deriving (Eq, Ord, Read, Show) I was hoping to get a min method defined in terms of the min method of the type argument (a). Instead, I think GHC is producing something

Re: Expected behavior of deriving Ord?

2008-03-19 Thread Duncan Coutts
On Wed, 2008-03-19 at 14:11 -0700, Conal Elliott wrote: I have an algebraic data type (not newtype) that derives Ord: data AddBounds a = MinBound | NoBound a | MaxBound deriving (Eq, Ord, Read, Show) I was hoping to get a min method defined in terms of the min method

Re: Expected behavior of deriving Ord?

2008-03-19 Thread Conal Elliott
, Mar 19, 2008 at 2:35 PM, Duncan Coutts [EMAIL PROTECTED] wrote: On Wed, 2008-03-19 at 14:11 -0700, Conal Elliott wrote: I have an algebraic data type (not newtype) that derives Ord: data AddBounds a = MinBound | NoBound a | MaxBound deriving (Eq, Ord, Read, Show) I

Re: [Haskell] recursive deriving

2007-11-21 Thread Lennart Augustsson
you want automated deriving of show/read etc., you need all the components of your type also to be instances of show/read but you won't want to *require* them to be automatically generated verions. Standalone deriving does the wrong thing here. Standalone deriving should not cause

Re: [Haskell] recursive deriving

2007-11-20 Thread Duncan Coutts
On Tue, 2007-11-20 at 19:18 -0500, Alex Jacobson wrote: When you want automated deriving of show/read etc., you need all the components of your type also to be instances of show/read but you won't want to *require* them to be automatically generated verions. Standalone deriving does

Re: [Haskell-cafe] Re: [Haskell] recursive deriving

2007-11-20 Thread Don Stewart
duncan.coutts: On Tue, 2007-11-20 at 19:18 -0500, Alex Jacobson wrote: When you want automated deriving of show/read etc., you need all the components of your type also to be instances of show/read but you won't want to *require* them to be automatically generated verions. Standalone

RE: Generalized newtype deriving 6.6 vs. 6.8

2007-11-05 Thread Simon Peyton-Jones
Well it's debatable. Suppose we have newtype Foo = MkFoo String deriving( Num ) Do you want to generate instance Num String = Num Foo ? I suspect not -- usually we generate an error message right away if we need a Num String instance and one is not available. Now you could argue

Re: Generalized newtype deriving 6.6 vs. 6.8

2007-11-05 Thread Isaac Dupree
Simon Peyton-Jones wrote: Well it's debatable. Suppose we have newtype Foo = MkFoo String deriving( Num ) Do you want to generate instance Num String = Num Foo ? Personally, I think I would like that -- along with a warning message. It makes it clearer to me that I can do newtype

Generalized newtype deriving 6.6 vs. 6.8

2007-11-03 Thread Twan van Laarhoven
Hello, I noticed there is a difference in generalized newtype deriving between 6.6 and 6.8. In GHC 6.4.1 the following: {-# LANGUAGE GeneralizedNewtypeDeriving #-} import Control.Monad.Error newtype MyMonad m a = MyMonad (m a) deriving (Monad, MonadError String) correctly gives

Change to deriving in 6.7 ??

2007-08-16 Thread Conal Elliott
I'm running ghc-6.7.20070802 and getting a new error message that didn't show up with ghc-6.6. Code: -- | Pairing for unary type constructors. newtype Pair1 f g a = Pair1 {unPair1 :: (f a, g a)} deriving (Eq, Ord, Show) Error message: src/Data/Tupler.hs:26:0: No instances

RE: GADT + Newtype deriving = Erroneous errors

2007-03-29 Thread Simon Peyton-Jones
Right. There are two things going on in this thread. First, when you say newtype T = MkT Int then T and Int are distinct types. Adding a deriving( whatever ) doesn't change that fact. Earlier messages make this point. The second is that GHC's current newtype deriving mechanism

Re: GADT + Newtype deriving = Erroneous errors

2007-03-29 Thread Fawzi Mohamed
Simon Peyton-Jones wrote: Generally speaking GHC will inline *across* modules just as much as it does *within* modules, with a single large exception. If GHC sees that a function 'f' is called just once, it inlines it regardless of how big 'f' is. But once 'f' is exported, GHC can never

Re: GADT + Newtype deriving = Erroneous errors

2007-03-28 Thread Tomasz Zielonka
deriving(IsIntC) I think newtype deriving should be rejected in this case. Maybe this is the real problem here? Best regards Tomek ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell

Re: GADT + Newtype deriving = Erroneous errors

2007-03-28 Thread Chris Kuklewicz
= Foo Int deriving(IsIntC) I think newtype deriving should be rejected in this case. Maybe this is the real problem here? Best regards Tomek On reflection, I agree. The derived instance would have to be instance IsIntC Foo where isInt :: IsIntT Foo isInt = isIntT which cannot

Re: GADT + Newtype deriving = Erroneous errors

2007-03-28 Thread Stefan O'Rear
On Wed, Mar 28, 2007 at 12:03:41PM +0100, Chris Kuklewicz wrote: Stefan O'Rear wrote: On Tue, Mar 27, 2007 at 11:32:29AM +0100, Chris Kuklewicz wrote: Stefan O'Rear wrote: newtype Foo = Foo Int deriving(IsIntC) Note that (Foo 2) + 2 is an attempt to add a Foo and an Int, which

Re: GADT + Newtype deriving = Erroneous errors

2007-03-27 Thread Chris Kuklewicz
]:/tmp$ cat A.lhs {-# OPTIONS_GHC -fglasgow-exts #-} data IsIntT x where IsIntT :: IsIntT Int class IsIntC a where isInt :: IsIntT a instance IsIntC Int where isInt = IsIntT newtype Foo = Foo Int deriving(IsIntC) x :: IsIntT Foo - Int x IsIntT = (Foo 2) + 2 IsIntT Foo is a concrete type

Re: GADT + Newtype deriving = Erroneous errors

2007-03-27 Thread Stefan O'Rear
ago to solve all the EnumMap performance concerns.) [EMAIL PROTECTED]:/tmp$ cat A.lhs {-# OPTIONS_GHC -fglasgow-exts #-} data IsIntT x where IsIntT :: IsIntT Int class IsIntC a where isInt :: IsIntT a instance IsIntC Int where isInt = IsIntT newtype Foo = Foo Int deriving(IsIntC

Re: GADT + Newtype deriving = Erroneous errors

2007-03-27 Thread Matthew Brecknell
Stefan O'Rear: They are the same type, and I have Curry-Howard proof of this fact. If that's the case, then it begs the question why you'd bother defining Foo in the first place. How would this solve EnumMap performance concerns? I am under the impression that newtypes are *defined* to be

Re: newtype deriving clause ceases to work in HEAD

2006-12-01 Thread Mathieu Boespflug
GHC 6.4.1 accepts your declaration but generates a useless insatance decl. GHC 6.6 will still let you generate the same instance, but only if you use another type variable, for instance deriving (MonadReader x) GHC 6.6's behaviour is defined by the appropriate section of the user

newtype deriving clause ceases to work in HEAD

2006-11-28 Thread Mathieu Boespflug
Hi, The following code compiles with GHC 6.4.2, but does not typecheck with GHC HEAD pulled on Sunday. module CompilerMonad where import Control.Monad import Control.Monad.Reader import Control.Monad.Error newtype CompilerError = CE String deriving Error newtype CM r a = CM (ReaderT r

RE: Proposal for stand-alone deriving declarations?

2006-11-01 Thread Simon Peyton-Jones
The thread about stand-alone deriving is long-ish now, so I have summarised the issues here: http://haskell.org/haskellwiki/GHC/StandAloneDeriving Perhaps those who are interested can add their thoughts? Bjorn is busy at the moment, but I think he'll get back to the implementation

deriving existential types

2006-05-04 Thread Marc Weber
) = CObj c deriving (C) ? - ? Or is this already possible? Marc Weber ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

RE: option for enabling generalized deriving for newtypes

2005-07-11 Thread Simon Peyton-Jones
Jeltsch | Sent: 10 July 2005 18:43 | To: GHC Users ML | Subject: option for enabling generalized deriving for newtypes | | Hello, | | isn't there an option for enabling just generalized deriving for newtypes | without enabling all this other stuff by using -fglasgow-exts? | | Best wishes, | Wolfgang

option for enabling generalized deriving for newtypes

2005-07-10 Thread Wolfgang Jeltsch
Hello, isn't there an option for enabling just generalized deriving for newtypes without enabling all this other stuff by using -fglasgow-exts? Best wishes, Wolfgang ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http

Re: deriving...

2004-10-20 Thread Martin Sjögren
On Tue, 19 Oct 2004 15:56:01 +0100 (BST), MR K P SCHUPKE [EMAIL PROTECTED] wrote: * I'm not at all keen on making '..deriving( Foo )' mean $(derive 'Foo) or something like that. Just make the TH call yourself! The current situation is that the code that generates the derived

RE: deriving...

2004-10-20 Thread Simon Peyton-Jones
have to be instance Typeable (T a) deriving or derive instance Typeable (T a) Something to clearly signal the magic. The trouble is, as you mention, that instance decls usually have a context. I'd be quite happy to require a context in these derived instances too, so you have to write derive

Re: deriving...

2004-10-20 Thread Christian Maeder
deriving instances will only work for a) known/builtin classes (like Typeable, Eq, Show, etc) b) datatypes T that are defined elsewhere using data (or newtype) where the corresponding deriving clause is missing. HTH Christian MR K P SCHUPKE wrote: instance Typeable (T a) Forgive my stupid

Re: deriving...

2004-10-20 Thread Andres Loeh
Typeable (T a) deriving Perhaps it would be not much harder to allow instance Show MyChar deriving where showList = ... to partially override derived functions as well. The trouble is, as you mention, that instance decls usually have a context. I'd be quite happy to require a context

Re: deriving...

2004-10-20 Thread MR K P SCHUPKE
As posted on this list, there is template-haskell code to do: $(derive [| data Foo = Foo |]) You can also get the type of Foo in TH by doing: dummy :: Foo dummy = undefined $(derive2 dummy) and the code for derive2 reify's the argument, which then gives the reflected type... so the example

Re: deriving...

2004-10-20 Thread Dylan Thurston
On Tue, Oct 19, 2004 at 08:08:49PM +0200, Andres Loeh wrote: Simon Peyton-Jones wrote: derive( Typeable (T a) ) But that means adding 'derive' as a keyword. Other possibilities: deriving( Typeable (T a) ) ... Any other ideas? instance Typeable (T a) deriving Why

RE: deriving...

2004-10-19 Thread Simon Peyton-Jones
Thanks to those who responded to this thread about 'deriving'. My current thoughts are: * I'd be happy to add the ability to separate a 'deriving' clause from its data type declaration, if we can agree syntax (see below). It's fairly easy to do; it makes the language more orthogonal

Re: deriving...

2004-10-19 Thread Christian Maeder
Simon Peyton-Jones wrote: derive( Typeable (T a) ) But that means adding 'derive' as a keyword. Other possibilities: deriving( Typeable (T a) ) -- (B) Re-use 'deriving' keyword The trouble with (B) is that the thing inside the parens is different in this situation than in a data type

Re: deriving...

2004-10-19 Thread Andres Loeh
Simon Peyton-Jones wrote: derive( Typeable (T a) ) But that means adding 'derive' as a keyword. Other possibilities: deriving( Typeable (T a) ) -- (B) Re-use 'deriving' keyword The trouble with (B) is that the thing inside the parens is different in this situation than

Re: deriving...

2004-10-17 Thread Keean Schupke
Okay so that does the deriving... How are you deriving the constraints? (in the ghc code there is some equaion expansion, where it finds the fixed point). Still the main point was that it would be nice to seamlessly integrate this... Surely it wouldn't take much to get the compiler to look

Re: deriving...

2004-10-17 Thread Ulf Norell
Keean Schupke [EMAIL PROTECTED] writes: Yes, I could quite easily write the generator in TemplateHaskell (have played with it before) _but_ I don't like the $(xxx) syntax... Perhaps if Simon could be persuaded to allow deriving clauses to be defined in TH? data X x = X x $(deriveMyClass

Re: deriving...

2004-10-16 Thread Shae Matijs Erisson
Keean Schupke [EMAIL PROTECTED] writes: Yes, I could quite easily write the generator in TemplateHaskell (have played with it before) _but_ I don't like the $(xxx) syntax... Perhaps if Simon could be persuaded to allow deriving clauses to be defined in TH? data X x = X x $(deriveMyClass

Re: deriving...

2004-10-16 Thread MR K P SCHUPKE
Check out Ulf Norell's IOHCC submission, his DeriveData.hs module does this, Do you have a link? Keean. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: deriving...

2004-10-16 Thread Shae Matijs Erisson
MR K P SCHUPKE [EMAIL PROTECTED] writes: Check out Ulf Norell's IOHCC submission, his DeriveData.hs module does this, Do you have a link? Yes, it's here: http://www.scannedinavian.org/iohcc/succzeroth-2004/ulfn.tar.gz -- Shae Matijs Erisson - Programmer - http://www.ScannedInAvian.org/ I

deriving...

2004-10-13 Thread MR K P SCHUPKE
What is the situation with deriving? Some instances can be derived automatically for both data/newtype (built in)? Some instances cen be derived automatically for newtype (any)? You used to be able to define functions useing {|+|} and {|*|} (or similar) that could be derived for both data

RE: deriving...

2004-10-13 Thread Simon Peyton-Jones
] On Behalf Of MR K P SCHUPKE | Sent: 13 October 2004 14:06 | To: [EMAIL PROTECTED] | Subject: deriving... | | | What is the situation with deriving? | | Some instances can be derived automatically for both data/newtype (built in)? | | Some instances cen be derived automatically for newtype (any

RE: deriving...

2004-10-13 Thread MR K P SCHUPKE
look at the user manual. Okay, I see the Generic type class stuff does not support multi parameter type classes. I guess I am stuck - any suggestions as to how best do this? I wish to be able to derive type level labels for datatypes, like the following: data Fred a = Fred a deriving

Re: deriving...

2004-10-13 Thread Andre Pang
a deriving TTypeable generates the instance: instance TTypeable a al = TTypeable (Fred a) (NCons (N3 (N4 (N5 Nil))) (TCons al Nil)) If you are happy to live on the edge a bit (which you seem to be happy with, considering that you're playing with GHC CVS ;), Template Haskell might be one way

Re: deriving...

2004-10-13 Thread Keean Schupke
Yes, I could quite easily write the generator in TemplateHaskell (have played with it before) _but_ I don't like the $(xxx) syntax... Perhaps if Simon could be persuaded to allow deriving clauses to be defined in TH? data X x = X x $(deriveMyClass (reify X)) could perhaps be defined from data X

deriving

2004-10-08 Thread MR K P SCHUPKE
How is deriving coded in ghc. For example the Typeable class, when in the compilation sequence is this expanded? Which modules do this, and which functions? Keean. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org

RE: deriving

2004-10-08 Thread Simon Peyton-Jones
] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of MR K P SCHUPKE | Sent: 08 October 2004 14:26 | To: [EMAIL PROTECTED] | Subject: deriving | | | How is deriving coded in ghc. For example the Typeable class, when in | the compilation sequence is this expanded? Which modules do

RE: deriving Typeable

2004-07-21 Thread Simon Peyton-Jones
| newtype Y e = Y { unY :: (e (Y e)) } | deriving(Data,Typeable,Show,Read,Eq) | | gives | E.hs:64: | Can't make a derived instance of `Typeable (Y e)' | (`Y' is parameterised over arguments of kind other than `*') | When deriving instances for type `Y' | | Is there any way around

RE: deriving Typeable

2004-06-03 Thread Simon Peyton-Jones
Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of John Meacham | Sent: 02 June 2004 21:53 | To: [EMAIL PROTECTED] | Subject: deriving Typeable | | newtype Y e = Y { unY :: (e (Y e)) } | deriving(Data,Typeable,Show,Read,Eq) | | gives | E.hs:64

deriving Typeable

2004-06-02 Thread John Meacham
newtype Y e = Y { unY :: (e (Y e)) } deriving(Data,Typeable,Show,Read,Eq) gives E.hs:64: Can't make a derived instance of `Typeable (Y e)' (`Y' is parameterised over arguments of kind other than `*') When deriving instances for type `Y' Is there any way around

RE: [Haskell] deriving with newtypes

2004-03-25 Thread Simon Peyton-Jones
Of Wolfgang | Jeltsch | Sent: 21 March 2004 17:55 | To: The Haskell Mailing List | Subject: [Haskell] deriving with newtypes | | Hello, | | I'm trying to use GHC's deriving mechanism for newtypes in the following way: | class C a b | instance C [a] Char | newtype T = T Char deriving C

Re: Using Template Haskell for deriving instances

2003-07-15 Thread Derek Elkins
. Unfortunately, this was back with 5.05 and I'm pretty sure the names and data structures have been changed. Hopefully, it's a relatively decent example of how to do this, it did seem to work at the time. When I work with TH again, I'd like to make a fairly general deriving framework, however gmap

RE: Conditions on deriving Typeable

2003-06-12 Thread Simon Peyton-Jones
It's a bug. Thank you Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] | On Behalf Of George Russell | Sent: 11 June 2003 13:07 | To: [EMAIL PROTECTED] | Subject: Conditions on deriving Typeable | | Please satisfy my curiosity, what is it about

RE: deriving weirdness on newtypes

2002-10-22 Thread Simon Peyton-Jones
| -Original Message- | From: Hal Daume III [mailto:hdaume;ISI.EDU] | Sent: 02 October 2002 18:58 | To: GHC Users Mailing List | Subject: deriving weirdness on newtypes | | So I love the fact that I can derive anything I want on | newtypes. However, there seem to be problems with it. If I

RE: deriving weirdness on newtypes

2002-10-08 Thread Simon Peyton-Jones
| newtype Foo = Foo Int deriving (Num) | instance Show Foo where { show = undefined } | | then, the value of 'show (Foo 5)' is undefined, but the value of 'show | (5::Foo)' is 5. definately *WRONG*. You're right. This is all a bit more complicated than I (or John H) thought

Re: deriving weirdness on newtypes

2002-10-03 Thread Ketil Z. Malde
Hal Daume III [EMAIL PROTECTED] writes: So I love the fact that I can derive anything I want on newtypes. However, there seem to be problems with it. If I write: newtype Foo = Foo Int deriving (Show) x = show (Foo 5) Then x is Foo 5 However, if I do newtype Foo = Foo

deriving weirdness on newtypes

2002-10-02 Thread Hal Daume III
So I love the fact that I can derive anything I want on newtypes. However, there seem to be problems with it. If I write: newtype Foo = Foo Int deriving (Show) x = show (Foo 5) Then x is Foo 5 However, if I do newtype Foo = Foo Int deriving (Num) x = show (Foo 5

RE: `deriving' cost

1999-02-22 Thread Simon Marlow
And the Simon's warning is for remembering that the effect is about as if one sets these instances manually. Do i understand correct? My point was merely that it's easy to forget how much code is needed for an instance of Show or Read, since it's easy (too easy :-) to stick 'deriving Show

RE: Existentially quantified types and ``deriving Eq''

1998-10-21 Thread Simon Peyton-Jones
The following datatype declaration would, if possible, actually be very useful for an application I have in mind: module Test(V(..)) where import ST data V s = forall a . MkV (STRef s a) deriving Eq Weird! You could never use the reference for anything, because its type

Re: Existentially quantified types and ``deriving Eq''

1998-10-21 Thread Lennart Augustsson
The correct behaviour would be to let the above pattern match fail in the case of different types at r1 and r2, because the left-hand side has to have a typing with equal types for r1 and r2 induced by the right-hand side ``r1 == r2''. But now you are assuming that there is an intentional