Re: [commit: packages/template-haskell] master: Make Pred a type synonym of Type (issue #7021) (57b662c)

2014-03-23 Thread Herbert Valerio Riedel
On 2014-03-23 at 04:40:14 +0100, Richard Eisenberg wrote:
 On Mar 22, 2014, at 9:05 PM, Mateusz Kowalczyk wrote:
  Is there a reason why the Template Haskell version wasn't bumped
 after this change?

 No -- I just didn't think of it. I won't have time in the next few
 days to do this (and validate, etc.), but I'll make this change soon.

Fyi, I went ahead and bumped to template-haskell to 2.10.0.0, fixed up
libraries/dph, and since ./validate still passed, I pushed the version
bump.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: [commit: packages/template-haskell] master: Make Pred a type synonym of Type (issue #7021) (57b662c)

2014-03-23 Thread Edward Kmett
Thanks. That'll let me make it clearer in my patches to work around the
this on my side that the source of the workarounds is the changes to the
template-haskell package.

-Edward


On Sun, Mar 23, 2014 at 5:37 AM, Herbert Valerio Riedel
hvrie...@gmail.comwrote:

 On 2014-03-23 at 04:40:14 +0100, Richard Eisenberg wrote:
  On Mar 22, 2014, at 9:05 PM, Mateusz Kowalczyk wrote:
   Is there a reason why the Template Haskell version wasn't bumped
  after this change?
 
  No -- I just didn't think of it. I won't have time in the next few
  days to do this (and validate, etc.), but I'll make this change soon.

 Fyi, I went ahead and bumped to template-haskell to 2.10.0.0, fixed up
 libraries/dph, and since ./validate still passed, I pushed the version
 bump.
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://www.haskell.org/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: [commit: packages/template-haskell] master: Make Pred a type synonym of Type (issue #7021) (57b662c)

2014-03-23 Thread Richard Eisenberg
Thanks, Herbert. I'll cross this off my to-do list.

Richard

On Mar 23, 2014, at 5:37 AM, Herbert Valerio Riedel hvrie...@gmail.com wrote:

 On 2014-03-23 at 04:40:14 +0100, Richard Eisenberg wrote:
 On Mar 22, 2014, at 9:05 PM, Mateusz Kowalczyk wrote:
 Is there a reason why the Template Haskell version wasn't bumped
 after this change?
 
 No -- I just didn't think of it. I won't have time in the next few
 days to do this (and validate, etc.), but I'll make this change soon.
 
 Fyi, I went ahead and bumped to template-haskell to 2.10.0.0, fixed up
 libraries/dph, and since ./validate still passed, I pushed the version
 bump.

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: [commit: packages/template-haskell] master: Make Pred a type synonym of Type (issue #7021) (57b662c)

2014-03-22 Thread Johan Tibell
What's the right way to fix libraries (e.g. aeson) that break because
classP was removed?


On Mon, Feb 10, 2014 at 2:39 AM, g...@git.haskell.org wrote:

 Repository : ssh://g...@git.haskell.org/template-haskell

 On branch  : master
 Link   :
 http://git.haskell.org/packages/template-haskell.git/commitdiff/57b662c3efd8579595c8642fce2d4cd60ba4ec0b

 ---

 commit 57b662c3efd8579595c8642fce2d4cd60ba4ec0b
 Author: YoEight yo.ei...@gmail.com
 Date:   Fri Jan 10 21:42:01 2014 +0100

 Make Pred a type synonym of Type (issue #7021)

 In order to make any type as a Predicate in Template Haskell, as
 allowed by ConstraintKinds

 Signed-off-by: Richard Eisenberg e...@cis.upenn.edu


 ---

 57b662c3efd8579595c8642fce2d4cd60ba4ec0b
  Language/Haskell/TH.hs|7 +++
  Language/Haskell/TH/Lib.hs|   21 -
  Language/Haskell/TH/Ppr.hs|8 ++--
  Language/Haskell/TH/Syntax.hs |6 ++
  4 files changed, 15 insertions(+), 27 deletions(-)

 diff --git a/Language/Haskell/TH.hs b/Language/Haskell/TH.hs
 index 2ab19bd..e9765a9 100644
 --- a/Language/Haskell/TH.hs
 +++ b/Language/Haskell/TH.hs
 @@ -68,7 +68,7 @@ module Language.Haskell.TH(
  -- ** Patterns
  Pat(..), FieldExp, FieldPat,
  -- ** Types
 -Type(..), TyVarBndr(..), TyLit(..), Kind, Cxt, Pred(..),
 Syntax.Role(..),
 +Type(..), TyVarBndr(..), TyLit(..), Kind, Cxt, Pred,
 Syntax.Role(..),

  -- * Library functions
  -- ** Abbreviations
 @@ -105,14 +105,14 @@ module Language.Haskell.TH(
  bindS, letS, noBindS, parS,

  -- *** Types
 -   forallT, varT, conT, appT, arrowT, listT, tupleT, sigT, litT,
 +   forallT, varT, conT, appT, arrowT, equalityT, listT, tupleT, sigT,
 litT,
  promotedT, promotedTupleT, promotedNilT, promotedConsT,
  --  Type literals
  numTyLit, strTyLit,
  --  Strictness
 isStrict, notStrict, strictType, varStrictType,
  --  Class Contexts
 -cxt, classP, equalP, normalC, recC, infixC, forallC,
 +cxt, normalC, recC, infixC, forallC,

  -- *** Kinds
varK, conK, tupleK, arrowK, listK, appK, starK, constraintK,
 @@ -146,4 +146,3 @@ module Language.Haskell.TH(
  import Language.Haskell.TH.Syntax as Syntax
  import Language.Haskell.TH.Lib
  import Language.Haskell.TH.Ppr
 -
 diff --git a/Language/Haskell/TH/Lib.hs b/Language/Haskell/TH/Lib.hs
 index b7a88d6..17e794b 100644
 --- a/Language/Haskell/TH/Lib.hs
 +++ b/Language/Haskell/TH/Lib.hs
 @@ -466,19 +466,6 @@ tySynEqn lhs rhs =
  cxt :: [PredQ] - CxtQ
  cxt = sequence

 -classP :: Name - [TypeQ] - PredQ
 -classP cla tys
 -  = do
 -  tys1 - sequence tys
 -  return (ClassP cla tys1)
 -
 -equalP :: TypeQ - TypeQ - PredQ
 -equalP tleft tright
 -  = do
 -  tleft1  - tleft
 -  tright1 - tright
 -  return (EqualP tleft1 tright1)
 -
  normalC :: Name - [StrictTypeQ] - ConQ
  normalC con strtys = liftM (NormalC con) $ sequence strtys

 @@ -536,6 +523,14 @@ sigT t k
t' - t
return $ SigT t' k

 +equalityT :: TypeQ - TypeQ - TypeQ
 +equalityT tleft tright
 +  = do
 +  tleft1  - tleft
 +  tright1 - tright
 +  let typ = AppT (AppT EqualityT tleft1) tright1
 +  return typ
 +
  promotedT :: Name - TypeQ
  promotedT = return . PromotedT

 diff --git a/Language/Haskell/TH/Ppr.hs b/Language/Haskell/TH/Ppr.hs
 index 2023f3a..e237066 100644
 --- a/Language/Haskell/TH/Ppr.hs
 +++ b/Language/Haskell/TH/Ppr.hs
 @@ -496,6 +496,8 @@ instance Ppr Type where

  pprTyApp :: (Type, [Type]) - Doc
  pprTyApp (ArrowT, [arg1,arg2]) = sep [pprFunArgType arg1 + text -,
 ppr arg2]
 +pprTyApp (EqualityT, [arg1, arg2]) =
 +sep [pprFunArgType arg1 + text ~, ppr arg2]
  pprTyApp (ListT, [arg]) = brackets (ppr arg)
  pprTyApp (TupleT n, args)
   | length args == n = parens (sep (punctuate comma (map ppr args)))
 @@ -540,11 +542,6 @@ pprCxt [t] = ppr t + text =
  pprCxt ts = parens (sep $ punctuate comma $ map ppr ts) + text =

  --
 -instance Ppr Pred where
 -  ppr (ClassP cla tys) = ppr cla + sep (map pprParendType tys)
 -  ppr (EqualP ty1 ty2) = pprFunArgType ty1 + char '~' + pprFunArgType
 ty2
 -
 ---
  instance Ppr Range where
  ppr = brackets . pprRange
  where pprRange :: Range - Doc
 @@ -569,4 +566,3 @@ hashParens d = text (#   d  text  #)

  quoteParens :: Doc - Doc
  quoteParens d = text '(  d  text )
 -
 diff --git a/Language/Haskell/TH/Syntax.hs b/Language/Haskell/TH/Syntax.hs
 index 3606f9d..17bb065 100644
 --- a/Language/Haskell/TH/Syntax.hs
 +++ b/Language/Haskell/TH/Syntax.hs
 @@ -1346,9 +1346,7 @@ data AnnTarget = ModuleAnnotation

  type Cxt = [Pred] -- ^ @(Eq a, Ord b)@

 -data Pred = ClassP Name [Type]-- ^ @Eq (Int, a)@
 -  | EqualP Type Type  -- ^ @F a ~ Bool@
 -  

Re: [commit: packages/template-haskell] master: Make Pred a type synonym of Type (issue #7021) (57b662c)

2014-03-22 Thread Mateusz Kowalczyk
On 22/03/14 20:37, Johan Tibell wrote:
 What's the right way to fix libraries (e.g. aeson) that break because
 classP was removed?
 

I have already patched lens, aeson, free, derive and binarydefer. You
can look for commits with my e-mail in those projects for how it was done.

All you need to do now to get aeson to compile on 7.9 is to get Bryan to
upload a new version with the relevant commit on Hackage.


-- 
Mateusz K.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: [commit: packages/template-haskell] master: Make Pred a type synonym of Type (issue #7021) (57b662c)

2014-03-22 Thread Richard Eisenberg
Note that the removal of `classP` is only for HEAD -- it will *not* be merged 
in for 7.8, which would be way too big a change at this point.

Richard

On Mar 22, 2014, at 4:53 PM, Mateusz Kowalczyk wrote:

 On 22/03/14 20:37, Johan Tibell wrote:
 What's the right way to fix libraries (e.g. aeson) that break because
 classP was removed?
 
 
 I have already patched lens, aeson, free, derive and binarydefer. You
 can look for commits with my e-mail in those projects for how it was done.
 
 All you need to do now to get aeson to compile on 7.9 is to get Bryan to
 upload a new version with the relevant commit on Hackage.
 
 
 -- 
 Mateusz K.
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://www.haskell.org/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: [commit: packages/template-haskell] master: Make Pred a type synonym of Type (issue #7021) (57b662c)

2014-03-22 Thread Richard Eisenberg

On Mar 22, 2014, at 9:05 PM, Mateusz Kowalczyk wrote:
  Is there a reason why the Template Haskell version wasn't bumped
 after this change?

No -- I just didn't think of it. I won't have time in the next few days to do 
this (and validate, etc.), but I'll make this change soon.

Thanks,
Richard
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs