RE: DoCon and GHC
Serge That's odd. I've tried with both 7.6 and HEAD, and both fail on T_cubeext thus: T_cubeext.hs:102:10: Overlapping instances for LinSolvRing (UPol k) arising from a use of `upEucRing' Matching instances: instance [overlap ok] EuclideanRing a = LinSolvRing (UPol a) -- Defined in `docon-2.12:Pol2_' instance [overlap ok] (LinSolvRing (Pol a), CommutativeRing a) = LinSolvRing (UPol (Pol a)) -- Defined in `docon-2.12:Pol3_' (The choice depends on the instantiation of `k' To pick the first instance above, use -XIncoherentInstances when compiling the other instance declarations) In the expression: upEucRing unA Map.empty In an equation for `dA': dA = upEucRing unA Map.empty I am using ghc-7.6 from Dec 3 (ie *later* than the released GHC 7.6.1), so perhaps the difference in error message is due to a bug in 7.6.1 that's fixed in my version. I suggest you use the 7.6.2 release candidate. Anyway, the error message looks entirely legitimate. It really does matter how 'k' is instantiated! I have no idea how it compiled before. The solution is to add (EuclideanRing k) to the type sig of cubicExt. Then it compiles all the way up to the top. Simon | -Original Message- | From: glasgow-haskell-bugs-boun...@haskell.org [mailto:glasgow-haskell- | bugs-boun...@haskell.org] On Behalf Of Serge D. Mechveliani | Sent: 21 December 2012 18:46 | To: Simon Peyton-Jones | Cc: glasgow-haskell-bugs@haskell.org | Subject: Re: DoCon and GHC | | On Fri, Dec 21, 2012 at 01:45:04PM +, Simon Peyton-Jones wrote: | OK, do this | | * {-# LANGUAGE ScopedTypeVariables, MonoLocalBinds #-} | | * import Categs( Domains1 ) | | * Add type sig for dP' | dP' :: (LinSolvRing (Pol a), CommutativeRing a) = Domains1 (Pol | a) | | Then it compiles. | | You are very close to the edge of what can be done! | | | It works. Thank you. | | There remains only a single unlucky module: T_cubeext. | The test demotest/Main works with exception of T_cubeext, but I need | T_cubeext.cubicExt to work. | | Please, continue the test with | | make install | cd demotest | ghc $doconCpOpt --make Main | | (for $doconCpOpt = | -fwarn-unused-matches -fwarn-unused-binds -fwarn-unused-imports | -fno-warn-overlapping-patterns -XRecordWildCards -XNamedFieldPuns | -XFlexibleContexts -XMultiParamTypeClasses -XUndecidableInstances | -XTypeSynonymInstances -XFlexibleInstances -XOverlappingInstances ). | | It reports | | -- | ... | T_cubeext.hs:102:20: | Could not deduce (k ~ k1) | from the context (Field k, FactorizationRing (UPol k)) | bound by the type signature for | cubicExt :: (Field k, FactorizationRing (UPol k)) = | k - k - Domains1 k - (Domains1 (E k), [E | k], k - E k) | at T_cubeext.hs:(79,13)-(80,69) | or from (Field k1, FactorizationRing (UPol k1)) | bound by the type signature for | unA :: (Field k1, FactorizationRing (UPol k1)) = UPol | k1 | at T_cubeext.hs:101:9-56 | `k' is a rigid type variable bound by | the type signature for | cubicExt :: (Field k, FactorizationRing (UPol k)) = | k - k - Domains1 k - (Domains1 (E k), [E k], | k - E k) | at T_cubeext.hs:79:13 | `k1' is a rigid type variable bound by |the type signature for | unA :: (Field k1, FactorizationRing (UPol k1)) = UPol k1 |at T_cubeext.hs:101:9 | Expected type: Domains1 k1 | Actual type: Domains1 k | In the second argument of `cToUPol', namely `dK' | In the expression: cToUPol d dK unK | In an equation for `unA': unA = cToUPol d dK unK | | T_cubeext.hs:105:7: | Overlapping instances for LinSolvRing (UPol k1) | arising from a use of `upEucRing' | Matching instances: | instance [overlap ok] EuclideanRing a = LinSolvRing (UPol a) | -- Defined in `docon-2.12:Pol2_' | instance [overlap ok] (LinSolvRing (Pol a), CommutativeRing a) = | LinSolvRing (UPol (Pol a)) ... | -- | | I tried {-# LANGUAGE ScopedTypeVariables, MonoLocalBinds #-}, and | setting type signatures in various parts in cubicExt. | But this does not help. | | There is another point. In | ``cubicExt :: (Field k, FactorizationRing (UPol k)) = ...'' | | the part ``, FactorizationRing (UPol k)'' (1) | | was always considered as parasitic. ghc-7.4.1 needs (1) to work, and | at least ghc-7.4.1 does compile the test. | | I thought, may be, the future compilers will allow to omit this part. | At least it is desirable for ghc-7.6.2 to do the test in any variant, | with (1) or without it. | | Regards, | | -- | Sergei
Re: DoCon and GHC
On Thu, Dec 20, 2012 at 07:57:45PM +, Simon Peyton-Jones wrote: | It looks like http://hackage.haskell.org | | is not valid now. Is this due to the recently announced e-mail lists | reorganization? It's working fine for me. No reorganisation there. Simon Today it is accessible for me two. And yesterday, I had access to http://haskell.org but not to http://hackage.haskell.org All right, may be sevaral middle servers where out. -- Sergei ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: DoCon and GHC
On Wed, Jun 20, 2012 at 04:56:01PM +, Simon Peyton-Jones wrote: Serge I hope you are well. I'm making a significant simplification to the type inference engine, which will have a small knock-on effect in DoCon. I implemented a VERY DELICATE HACK to solve your problem before, but it has become a significant problem to maintain the hack, so I'm taking it out. See http://hackage.haskell.org/trac/ghc/ticket/4361, and the comments I have added there, which tell you what change to make. It's very minor! This will take effect from GHC 7.6 onwards. Thanks Simon This is on Ticket #4361 (closed bug: fixed) about compiling DoCon. Its story is as follows. * 7.4.0 failed to compile the module Pol3_ in DoCon due to 1) a certain GHC manner of constraint simplification (as Simon wrote) 2) a due to complex enough constraints used in DoCon, in particular, instance (LinSolvRing (Pol a), CommutativeRing a) = LinSolvRing (UPol (Pol a)) set in Pol3_.hs (I do not know how to simplify this constraint without loosing generality). * 7.4.1 does compile it, but, as Simon wrote, applies for this a very specific and unstable compilation method. * 7.6+ removes this latter method, and Simon P. Jones concludes Happily, it's extremely easy to fix your source code in either of these two ways: * If you use -XMonoLocalBinds (which is in any case implied by -XGADTs and -XTypeFamilies), then GHC won't generalise the definition of x in the example, and all will be well. * Alterantively, give a type signature for x, thus (in this case) moduloBasisx p = let x :: () x = upLinSolvRing p in () Now, I am trying ghc-7.6.1.20121207 built from source on Debian Linux. I. I try adding -XMonoLocalBinds for compiling DoCon: -- doco.cabal --- ... ghc-options: -fno-warn-overlapping-patterns -fwarn-unused-binds -fwarn-unused-matches -fwarn-unused-imports -XMonoLocalBinds -O -- `make build' fails at the first module: -- module Prelude_ where ... instance (DShow a, DShow b) = DShow (a, b) ... where dShows opts (x, y) = showChar '(' . shows1 x . showString sep . shows1 y . showChar ')' -- line 628 where opts'= addToShowOptions (- 1) $ opts {parInShow = Parens} sep = fieldSeparator opts shows1 x = (case parInShow opts of Parens - id _ - unparensUpper ()) . dShows opts' x aShows (a, b) = showString (pair . aShows a . showChar ' ' . aShows b . showChar ')' -- The report is runghc Setup.hs build Building docon-2.12... Preprocessing library docon-2.12... [ 1 of 84] Compiling Prelude_ ( Prelude_.hs, dist/build/Prelude_.o ) Prelude_.hs:628:32: Could not deduce (a ~ b) from the context (DShow a, DShow b) bound by the instance declaration at Prelude_.hs:622:10-43 `a' is a rigid type variable bound by the instance declaration at Prelude_.hs:622:10 `b' is a rigid type variable bound by the instance declaration at Prelude_.hs:622:10 In the first argument of `shows1', namely `y' In the first argument of `(.)', namely `shows1 y' In the second argument of `(.)', namely shows1 y . showChar ')' ... --- The line 628 is marked in the code as -- line 628. I suspect that besides -XMonoLocalBinds, I need also to add some explicit type signatures, for example, dShows opts (x, y) = showChar '(' . shows1 (x :: DShow a = a) . ... Because GHC, probably, finds some contradiction in applying shows1 to x :: a and to y :: b. II. My another attempt will be removing -XMonoLocalBinds (with this, it compiles many modules and stops at Pol3.hs) and inserting a type signature in an appropriate place (this will also need to add ScopedTypeVariables + `forall' -- thanks to people for hints ). If (II) works, then it will be, probably less restrictive than (I). This is just the current report of my attempt to compile DoCon with GHC. -- Sergei ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: DoCon and GHC
I would not use -XMonoLocalBinds for all modules -- that will force you to do more work. Instead use it just for the offending Pol3_ module, via {-# LANGUAGE MonoLocalBinds #-} Or, probably better, give a type signature inside moduloBasisx, as suggested in the http://hackage.haskell.org/trac/ghc/ticket/4361. The signature is better because it also makes the program easier to understand! Simon | -Original Message- | From: Serge D. Mechveliani [mailto:mech...@botik.ru] | Sent: 21 December 2012 10:08 | To: Simon Peyton-Jones | Cc: glasgow-haskell-bugs@haskell.org | Subject: Re: DoCon and GHC | | On Wed, Jun 20, 2012 at 04:56:01PM +, Simon Peyton-Jones wrote: | Serge | | I hope you are well. | | I'm making a significant simplification to the type inference engine, | which will have a small knock-on effect in DoCon. | | I implemented a VERY DELICATE HACK to solve your problem before, but | it has become a significant problem to maintain the hack, so I'm | taking it out. | | See http://hackage.haskell.org/trac/ghc/ticket/4361, and the comments | I have added there, which tell you what change to make. It's very | minor! | | This will take effect from GHC 7.6 onwards. Thanks | | Simon | | | This is on Ticket #4361 (closed bug: fixed) | about compiling DoCon. | | Its story is as follows. | | * 7.4.0 failed to compile the module Pol3_ in DoCon due to | 1) a certain GHC manner of constraint simplification (as Simon | wrote) | 2) a due to complex enough constraints used in DoCon, in particular, | instance (LinSolvRing (Pol a), CommutativeRing a) = | LinSolvRing (UPol (Pol a)) | set in Pol3_.hs | (I do not know how to simplify this constraint without loosing | generality). | | * 7.4.1 does compile it, but, as Simon wrote, applies for this a very | specific and unstable compilation method. | * 7.6+ removes this latter method, and Simon P. Jones concludes | | Happily, it's extremely easy to fix your source code in either of | these two ways: | | * If you use -XMonoLocalBinds (which is in any case implied by -XGADTs |and -XTypeFamilies), then GHC won't generalise the definition of x | in the example, and all will be well. | | * Alterantively, give a type signature for x, thus (in this case) | |moduloBasisx p = let x :: () | x = upLinSolvRing p | in () | | | | Now, I am trying ghc-7.6.1.20121207 built from source on Debian Linux. | | | I. I try adding -XMonoLocalBinds for compiling DoCon: | | | -- doco.cabal --- ... | ghc-options: | -fno-warn-overlapping-patterns -fwarn-unused-binds | -fwarn-unused-matches -fwarn-unused-imports -XMonoLocalBinds | -O | -- | | `make build' fails at the first module: | | -- | module Prelude_ | where | ... | instance (DShow a, DShow b) = DShow (a, b) | ... | where | dShows opts (x, y) = showChar '(' . shows1 x . showString sep . | shows1 y . showChar ')' -- | line 628 | where | opts'= addToShowOptions (- 1) $ opts {parInShow = Parens} | sep = fieldSeparator opts | shows1 x = (case parInShow opts of Parens - id |_ - unparensUpper ()) |. dShows opts' x | | aShows (a, b) = showString (pair . aShows a . showChar ' ' . |aShows b . showChar ')' | -- | | The report is | | runghc Setup.hs build | Building docon-2.12... | Preprocessing library docon-2.12... | [ 1 of 84] Compiling Prelude_ ( Prelude_.hs, | dist/build/Prelude_.o ) | | Prelude_.hs:628:32: | Could not deduce (a ~ b) | from the context (DShow a, DShow b) | bound by the instance declaration at Prelude_.hs:622:10-43 | `a' is a rigid type variable bound by | the instance declaration at Prelude_.hs:622:10 | `b' is a rigid type variable bound by | the instance declaration at Prelude_.hs:622:10 | In the first argument of `shows1', namely `y' | In the first argument of `(.)', namely `shows1 y' | In the second argument of `(.)', namely shows1 y . showChar ')' | ... | --- | | The line 628 is marked in the code as -- line 628. | | | I suspect that besides -XMonoLocalBinds, I need also to add some | explicit type signatures, for example, | dShows opts (x, y) = showChar '(' . shows1 (x :: DShow a = a) . |... | | Because GHC, probably, finds some contradiction in applying shows1 to | x :: a and to y :: b. | | | II. My another attempt will be removing -XMonoLocalBinds | (with this, it compiles many modules and stops at Pol3.hs
Re: DoCon and GHC
On Fri, Dec 21, 2012 at 10:12:38AM +, Simon Peyton-Jones wrote: I would not use -XMonoLocalBinds for all modules -- that will force you to do more work. Instead use it just for the offending Pol3_ module, via {-# LANGUAGE MonoLocalBinds #-} Or, probably better, give a type signature inside moduloBasisx, as suggested in the http://hackage.haskell.org/trac/ghc/ticket/4361. The signature is better because it also makes the program easier to understand! Simon [..] | * Alterantively, give a type signature for x, thus (in this case) | |moduloBasisx p = let x :: () | x = upLinSolvRing p | in () Now, I am trying ghc-7.6.1.20121207 built from source on Debian Linux. -- docon.cabal - ... extensions: TypeSynonymInstances UndecidableInstances FlexibleContexts FlexibleInstances MultiParamTypeClasses OverlappingInstances RecordWildCards NamedFieldPuns DoAndIfThenElse . ghc-options: -fno-warn-overlapping-patterns -fwarn-unused-binds -fwarn-unused-matches -fwarn-unused-imports -XRankNTypes -- new -O --- `make build' fails at Pol3_.hs, at compiling this instance -- Pol3_.hs ... {-# LANGUAGE ScopedTypeVariables #-}-- (1) ** instance forall a. (LinSolvRing (Pol a), CommutativeRing a) = -- (2) ** LinSolvRing (UPol (Pol a)) where -- gxBasis in P[y], P = a[x1..xn]. -- Map to a[y,x1..xn] apply gxBasis there, return to P: gxBasis [] = ([], []) gxBasis fs@(f:_) = (map back gs, mapmap back mt) where UPol _ p y dP= f (o, n) = (pPPO p, genLength $ pVars p) (toLex, fromLex) = (reordPol $ lexPPO n, reordPol o) p' = (toLex p) `asTypeOf` p -- (3) ** dP' :: forall a. (LinSolvRing (Pol a), CommutativeRing a) = -- (4) ** Domains1 (Pol a) dP' = upLinSolvRing p' Map.empty -- p needs lexPPO reordering, then, -- its domain bundle needs change too s' = cToUPol y dP' p' -- sample for P'[y], P' = a[x1..xn] with lexComp toOverP' = ct s' . map (\ (a, j) - (toLex a, j)) . upolMons fromOverP' = ct f . map (\ (a, j) - (fromLex a, j)) . upolMons -- P[y] -- P'[y] back = fromOverP' . headVarPol dP (gs, mt) = gxBasis $ map (fromHeadVarPol . toOverP') fs - What is newly added: 1) -XRankNTypes to docon.cabal -- in order to allow `forall' to `instance'. 2) {-# LANGUAGE ScopedTypeVariables #-} -- to support explicit polymorphic type signatures in the instance implementation, 3) asTypeOf for p', 4) Explicit signature for dP'. The report is similar as the old one: Pol3_.hs:328:25: Could not deduce (a ~ a1) from the context (CommutativeRing (UPol (Pol a)), MulMonoid (UPol (Pol a)), LinSolvRing (Pol a), CommutativeRing a) bound by the instance declaration at Pol3_.hs:(313,10)-(314,72) or from (LinSolvRing (Pol a1), CommutativeRing a1) bound by the type signature for dP' :: (LinSolvRing (Pol a1), CommutativeRing a1) = Domains1 (Pol a1) at Pol3_.hs:327:12-71 `a' is a rigid type variable bound by the instance declaration at Pol3_.hs:313:17 `a1' is a rigid type variable bound by the type signature for dP' :: (LinSolvRing (Pol a1), CommutativeRing a1) = Domains1 (Pol a1) at Pol3_.hs:327:12 Expected type: Pol a1 Actual type: Pol a In the first argument of `upLinSolvRing', namely p' In the expression: upLinSolvRing p' Map.empty In an equation for dP': dP' = upLinSolvRing p' Map.empty Pol3_.hs:331:20: Could not deduce (EuclideanRing a) arising from a use of dP' from the context (CommutativeRing (UPol (Pol a)), MulMonoid (UPol (Pol a)), LinSolvRing (Pol a), CommutativeRing a) bound by the instance declaration at Pol3_.hs:(313,10)-(314,72) Possible fix: add (EuclideanRing a) to the context of the instance declaration In the second argument of `cToUPol', namely dP' In the expression: cToUPol y dP' p' In an equation for s': s' = cToUPol y dP' p' - ghc-7.4.1 compiles everything without additions. Can
Re: DoCon and GHC
On Fri, Dec 21, 2012 at 11:26:30AM +, Simon Peyton-Jones wrote: I think you need to remove the 'forall a' on the type signature for dP'. The 'a' you mean is the 'a' from the instance declaration, not a completely fresh 'a'. This looks reasonable. Moreover I don't think you need the 'forall' on the 'instance' declaration. Just 'ScopedTypeVariables' should do it All right, I try to follow both instructions: -- docon.cabal - ... extensions: TypeSynonymInstances UndecidableInstances FlexibleContexts FlexibleInstances MultiParamTypeClasses OverlappingInstances RecordWildCards NamedFieldPuns DoAndIfThenElse . ghc-options: -fno-warn-overlapping-patterns -fwarn-unused-binds -fwarn-unused-matches -fwarn-unused-imports -XRankNTypes -- ** probably, it spoils nothing -O --- -- Pol3_.hs ... {-# LANGUAGE ScopedTypeVariables #-}-- (1) ** instance (LinSolvRing (Pol a), CommutativeRing a) = LinSolvRing (UPol (Pol a)) where gxBasis [] = ([], []) gxBasis fs@(f:_) = (map back gs, mapmap back mt) where UPol _ p y dP= f (o, n) = (pPPO p, genLength $ pVars p) (toLex, fromLex) = (reordPol $ lexPPO n, reordPol o) p' = (toLex p) `asTypeOf` p -- (2) ** dP' :: (LinSolvRing (Pol a), CommutativeRing a) = -- (3) ** Domains1 (Pol a) dP' = upLinSolvRing p' Map.empty s' = cToUPol y dP' p' toOverP' = ct s' . map (\ (a, j) - (toLex a, j)) . upolMons fromOverP' = ct f . map (\ (a, j) - (fromLex a, j)) . upolMons back = fromOverP' . headVarPol dP (gs, mt) = gxBasis $ map (fromHeadVarPol . toOverP') fs - This does not help: - Pol3_.hs:328:25: Could not deduce (a ~ a1) from the context (CommutativeRing (UPol (Pol a)), MulMonoid (UPol (Pol a)), LinSolvRing (Pol a), CommutativeRing a) bound by the instance declaration at Pol3_.hs:(313,10)-(314,72) or from (LinSolvRing (Pol a1), CommutativeRing a1) bound by the type signature for dP' :: (LinSolvRing (Pol a1), CommutativeRing a1) = Domains1 (Pol a1) at Pol3_.hs:327:12-71 `a' is a rigid type variable bound by the instance declaration at Pol3_.hs:313:10 `a1' is a rigid type variable bound by the type signature for dP' :: (LinSolvRing (Pol a1), CommutativeRing a1) = Domains1 (Pol a1) at Pol3_.hs:327:12 Expected type: Pol a1 Actual type: Pol a In the first argument of `upLinSolvRing', namely p' In the expression: upLinSolvRing p' Map.empty In an equation for dP': dP' = upLinSolvRing p' Map.empty Pol3_.hs:331:20: Could not deduce (EuclideanRing a) arising from a use of dP' from the context (CommutativeRing (UPol (Pol a)), MulMonoid (UPol (Pol a)), LinSolvRing (Pol a), CommutativeRing a) bound by the instance declaration at Pol3_.hs:(313,10)-(314,72) Possible fix: add (EuclideanRing a) to the context of the instance declaration In the second argument of `cToUPol', namely dP' In the expression: cToUPol y dP' p' In an equation for s': s' = cToUPol y dP' p' -- Regards, -- Sergei ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: DoCon and GHC
On Fri, Dec 21, 2012 at 01:45:04PM +, Simon Peyton-Jones wrote: OK, do this * {-# LANGUAGE ScopedTypeVariables, MonoLocalBinds #-} * import Categs( Domains1 ) * Add type sig for dP' dP' :: (LinSolvRing (Pol a), CommutativeRing a) = Domains1 (Pol a) Then it compiles. You are very close to the edge of what can be done! It works. Thank you. There remains only a single unlucky module: T_cubeext. The test demotest/Main works with exception of T_cubeext, but I need T_cubeext.cubicExt to work. Please, continue the test with make install cd demotest ghc $doconCpOpt --make Main (for $doconCpOpt = -fwarn-unused-matches -fwarn-unused-binds -fwarn-unused-imports -fno-warn-overlapping-patterns -XRecordWildCards -XNamedFieldPuns -XFlexibleContexts -XMultiParamTypeClasses -XUndecidableInstances -XTypeSynonymInstances -XFlexibleInstances -XOverlappingInstances ). It reports -- ... T_cubeext.hs:102:20: Could not deduce (k ~ k1) from the context (Field k, FactorizationRing (UPol k)) bound by the type signature for cubicExt :: (Field k, FactorizationRing (UPol k)) = k - k - Domains1 k - (Domains1 (E k), [E k], k - E k) at T_cubeext.hs:(79,13)-(80,69) or from (Field k1, FactorizationRing (UPol k1)) bound by the type signature for unA :: (Field k1, FactorizationRing (UPol k1)) = UPol k1 at T_cubeext.hs:101:9-56 `k' is a rigid type variable bound by the type signature for cubicExt :: (Field k, FactorizationRing (UPol k)) = k - k - Domains1 k - (Domains1 (E k), [E k], k - E k) at T_cubeext.hs:79:13 `k1' is a rigid type variable bound by the type signature for unA :: (Field k1, FactorizationRing (UPol k1)) = UPol k1 at T_cubeext.hs:101:9 Expected type: Domains1 k1 Actual type: Domains1 k In the second argument of `cToUPol', namely `dK' In the expression: cToUPol d dK unK In an equation for `unA': unA = cToUPol d dK unK T_cubeext.hs:105:7: Overlapping instances for LinSolvRing (UPol k1) arising from a use of `upEucRing' Matching instances: instance [overlap ok] EuclideanRing a = LinSolvRing (UPol a) -- Defined in `docon-2.12:Pol2_' instance [overlap ok] (LinSolvRing (Pol a), CommutativeRing a) = LinSolvRing (UPol (Pol a)) ... -- I tried {-# LANGUAGE ScopedTypeVariables, MonoLocalBinds #-}, and setting type signatures in various parts in cubicExt. But this does not help. There is another point. In ``cubicExt :: (Field k, FactorizationRing (UPol k)) = ...'' the part ``, FactorizationRing (UPol k)'' (1) was always considered as parasitic. ghc-7.4.1 needs (1) to work, and at least ghc-7.4.1 does compile the test. I thought, may be, the future compilers will allow to omit this part. At least it is desirable for ghc-7.6.2 to do the test in any variant, with (1) or without it. Regards, -- Sergei ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: DoCon and GHC
On Wed, Jun 20, 2012 at 04:56:01PM +, Simon Peyton-Jones wrote: Serge I hope you are well. I'm making a significant simplification to the type inference engine, which will have a small knock-on effect in DoCon. I implemented a VERY DELICATE HACK to solve your problem before, but it has become a significant problem to maintain the hack, so I'm taking it out. See http://hackage.haskell.org/trac/ghc/ticket/4361, and the comments I have added there, which tell you what change to make. It's very minor! This will take effect from GHC 7.6 onwards. Thanks Simon It looks like http://hackage.haskell.org is not valid now. Is this due to the recently announced e-mail lists reorganization? How can I see these comments on ticket 4361 ? Regards, Sergei ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: DoCon and GHC
| It looks like http://hackage.haskell.org | | is not valid now. Is this due to the recently announced e-mail lists | reorganization? It's working fine for me. No reorganisation there. Simon ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs