Hello community,
here is the log from the commit of package ghc-haskell-src-meta for
openSUSE:Factory checked in at 2017-08-31 20:47:27
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-haskell-src-meta (Old)
and /work/SRC/openSUSE:Factory/.ghc-haskell-src-meta.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-haskell-src-meta"
Thu Aug 31 20:47:27 2017 rev:3 rq:513367 version:0.8.0.1
Changes:
--------
---
/work/SRC/openSUSE:Factory/ghc-haskell-src-meta/ghc-haskell-src-meta.changes
2017-06-22 10:37:42.336355403 +0200
+++
/work/SRC/openSUSE:Factory/.ghc-haskell-src-meta.new/ghc-haskell-src-meta.changes
2017-08-31 20:47:28.663127816 +0200
@@ -1,0 +2,5 @@
+Thu Jul 27 14:03:02 UTC 2017 - [email protected]
+
+- Update to version 0.8.0.1.
+
+-------------------------------------------------------------------
Old:
----
haskell-src-meta-0.7.0.1.tar.gz
haskell-src-meta.cabal
New:
----
haskell-src-meta-0.8.0.1.tar.gz
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Other differences:
------------------
++++++ ghc-haskell-src-meta.spec ++++++
--- /var/tmp/diff_new_pack.u78ZBc/_old 2017-08-31 20:47:29.814966137 +0200
+++ /var/tmp/diff_new_pack.u78ZBc/_new 2017-08-31 20:47:29.818965576 +0200
@@ -17,15 +17,15 @@
%global pkg_name haskell-src-meta
+%bcond_with tests
Name: ghc-%{pkg_name}
-Version: 0.7.0.1
+Version: 0.8.0.1
Release: 0
Summary: Parse source to template-haskell abstract syntax
License: BSD-3-Clause
Group: Development/Languages/Other
Url: https://hackage.haskell.org/package/%{pkg_name}
Source0:
https://hackage.haskell.org/package/%{pkg_name}-%{version}/%{pkg_name}-%{version}.tar.gz
-Source1:
https://hackage.haskell.org/package/%{pkg_name}-%{version}/revision/1.cabal#/%{pkg_name}.cabal
BuildRequires: ghc-Cabal-devel
BuildRequires: ghc-haskell-src-exts-devel
BuildRequires: ghc-pretty-devel
@@ -34,6 +34,11 @@
BuildRequires: ghc-template-haskell-devel
BuildRequires: ghc-th-orphans-devel
BuildRoot: %{_tmppath}/%{name}-%{version}-build
+%if %{with tests}
+BuildRequires: ghc-HUnit-devel
+BuildRequires: ghc-test-framework-devel
+BuildRequires: ghc-test-framework-hunit-devel
+%endif
%description
The translation from haskell-src-exts abstract syntax to template-haskell
@@ -53,7 +58,6 @@
%prep
%setup -q -n %{pkg_name}-%{version}
-cp -p %{SOURCE1} %{pkg_name}.cabal
%build
%ghc_lib_build
@@ -61,6 +65,9 @@
%install
%ghc_lib_install
+%check
+%cabal_test
+
%post devel
%ghc_pkg_recache
++++++ haskell-src-meta-0.7.0.1.tar.gz -> haskell-src-meta-0.8.0.1.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/haskell-src-meta-0.7.0.1/ChangeLog
new/haskell-src-meta-0.8.0.1/ChangeLog
--- old/haskell-src-meta-0.7.0.1/ChangeLog 2017-01-11 14:37:22.000000000
+0100
+++ new/haskell-src-meta-0.8.0.1/ChangeLog 2017-05-31 20:40:48.000000000
+0200
@@ -1,9 +1,23 @@
+0.8.0.1
+- Bump base and template-haskell library to versions shipped with GHC 7.6.
+
+0.8
+- Compatibility with GHC 8.2.
+- Remove deprecated modules.
+
+0.7.0.1
+- Fixed a bug that caused deriving clauses to be ignored on TH 2.11.
+
+0.7.0
+- Compatibility with haskell-src-exts 1.18.
+- Support dropped for GHC < 7.6 and haskell-src-exts < 1.17.
+
0.6.0.14:
- Compatibility with GHC 8.0.
0.6.0.13:
- Compatibility with GHC HEAD, haskell-src-exts 1.17
-- Remove hsBindsToDecs, since it was redundant with toDecs. Technically this
+- Remove hsBindsToDecs, since it was redundant with toDecs. Technically this
requires a minor-version bump, but I doubt anyone was using it.
0.6.0.12:
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/haskell-src-meta-0.7.0.1/haskell-src-meta.cabal
new/haskell-src-meta-0.8.0.1/haskell-src-meta.cabal
--- old/haskell-src-meta-0.7.0.1/haskell-src-meta.cabal 2017-01-11
14:37:22.000000000 +0100
+++ new/haskell-src-meta-0.8.0.1/haskell-src-meta.cabal 2017-05-31
20:40:48.000000000 +0200
@@ -1,6 +1,6 @@
name: haskell-src-meta
-version: 0.7.0.1
-cabal-version: >= 1.6
+version: 0.8.0.1
+cabal-version: >= 1.8
build-type: Simple
license: BSD3
license-file: LICENSE
@@ -9,8 +9,7 @@
copyright: (c) Matt Morrow
maintainer: Ben Millwood <[email protected]>
bug-reports: https://github.com/bmillwood/haskell-src-meta/issues
--- That is to say, "builds with". It's not like we have a testsuite.
-tested-with: GHC == 7.6.3, GHC == 7.8.3, GHC == 7.10.3, GHC == 8.0.1
+tested-with: GHC == 7.6.3, GHC == 7.8.3, GHC == 7.10.3, GHC == 8.0.2,
GHC == 8.2.1
synopsis: Parse source to template-haskell abstract syntax.
description: The translation from haskell-src-exts abstract syntax
to template-haskell abstract syntax isn't 100% complete
yet.
@@ -18,31 +17,37 @@
extra-source-files: ChangeLog README.md examples/*.hs
library
- build-depends: base >= 4.5 && < 4.10,
- haskell-src-exts >= 1.17 && < 1.19,
+ build-depends: base >= 4.6 && < 4.11,
+ haskell-src-exts >= 1.17 && < 1.20,
pretty >= 1.0 && < 1.2,
- syb >= 0.1 && < 0.7,
- template-haskell >= 2.7 && < 2.12,
+ syb >= 0.1 && < 0.8,
+ template-haskell >= 2.8 && < 2.13,
th-orphans >= 0.9.1 && < 0.14
- extensions: CPP,
- RankNTypes,
- StandaloneDeriving,
- TemplateHaskell,
- TypeSynonymInstances,
- FlexibleContexts,
- FlexibleInstances,
- DeriveDataTypeable,
- PatternGuards
+ if impl(ghc < 7.8)
+ build-depends: safe <= 0.3.9
+
hs-source-dirs: src
exposed-modules: Language.Haskell.Meta
Language.Haskell.Meta.Parse
- Language.Haskell.Meta.Parse.Careful
Language.Haskell.Meta.Syntax.Translate
- Language.Haskell.TH.Instances.Lift
Language.Haskell.Meta.Utils
+test-suite unit
+ type: exitcode-stdio-1.0
+ hs-source-dirs: tests
+ main-is: Main.hs
+
+ build-depends:
+ HUnit >= 1.2 && < 1.7,
+ base >= 4.5 && < 4.11,
+ haskell-src-exts >= 1.17 && < 1.20,
+ haskell-src-meta,
+ pretty >= 1.0 && < 1.2,
+ template-haskell >= 2.7 && < 2.13,
+ test-framework >= 0.8 && < 0.9,
+ test-framework-hunit >= 0.3 && < 0.4
+
source-repository head
type: git
location: git://github.com/bmillwood/haskell-src-meta.git
-
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore'
old/haskell-src-meta-0.7.0.1/src/Language/Haskell/Meta/Parse/Careful.hs
new/haskell-src-meta-0.8.0.1/src/Language/Haskell/Meta/Parse/Careful.hs
--- old/haskell-src-meta-0.7.0.1/src/Language/Haskell/Meta/Parse/Careful.hs
2017-01-11 14:37:22.000000000 +0100
+++ new/haskell-src-meta-0.8.0.1/src/Language/Haskell/Meta/Parse/Careful.hs
1970-01-01 01:00:00.000000000 +0100
@@ -1,60 +0,0 @@
-{- |
-DEPRECATED: haskell-src-meta now requires GHC >= 7.4, so this module is no
longer necessary. It will be GHC-warning deprecated soon.
-
-This module provides the tools to handle operator fixities in infix
expressions correctly.
-
-The problem we solve is the following. Consider making a quasiquoter which
antiquotes to Haskell - for instance, the quasiquoter in
<http://hackage.haskell.org/package/hmatrix-static> allows me to write
-
-> myVec :: Vector Double
-> myVec = [vec| 2+3*4, 5-4-3 |]
-
-To correctly parse such expressions, we need to know the fixities and
precedences of the operators, so that the above is parsed the same way as
-
-> myVec = [vec| 2+(3*4), (5-4)-3 |]
-
-There is a danger, if we are not careful in parsing, that the above expression
instead parses as
-
-> myVec = [vec| (2+3)*4, 5-(4-3) |]
-
-which is a surprising bug, and would only be detected through testing at
runtime, rather than at compile time.
-
-When this danger arises, we use this \"careful\" module. It handles
\"unresolved infix\" expressions such as @2+3*4@ in two ways, depending on the
version of GHC:
-
- * in GHC 7.4 and above (where support for \"unresolved infix\" was added in
Template Haskell), resolution of the infix expression is deferred to the
compiler, which has all fixities available to it.
-
- * prior to GHC 7.4, any ambiguous infix expression is flagged as a parse
error at compile time, and the user is advised to resolve the ambiguity by
adding parentheses.
-
--}
-module Language.Haskell.Meta.Parse.Careful(
- parsePat,
- parseExp,
- parseType,
- parseDecs
- ) where
-
-import qualified Language.Haskell.Meta.Parse as Sloppy
-import qualified Language.Haskell.Meta.Syntax.Translate as Translate
-import qualified Language.Haskell.TH as TH
-import qualified Language.Haskell.Exts.Syntax as Hs
-
-doChecked parser translater p =
- case parser p of
- Left s -> Left s
- Right p' | amb p' -> Left "Infix expression could not be resolved as
operator fixities are not known. Resolve ambiguity by adding parentheses"
- | otherwise -> Right (translater p')
-
-parsePat :: String -> Either String TH.Pat
-parsePat = doChecked Sloppy.parseHsPat Translate.toPat
-
-parseExp :: String -> Either String TH.Exp
-parseExp = doChecked Sloppy.parseHsExp Translate.toExp
-
-parseType :: String -> Either String TH.Type
-parseType = doChecked Sloppy.parseHsType Translate.toType
-
-parseDecs :: String -> Either String [TH.Dec]
-parseDecs = doChecked Sloppy.parseHsDecls Translate.toDecs
-
--- This was more complicated, but since support for GHC pre-7.4 was dropped,
--- it's no longer necessary
-amb = const False
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore'
old/haskell-src-meta-0.7.0.1/src/Language/Haskell/Meta/Syntax/Translate.hs
new/haskell-src-meta-0.8.0.1/src/Language/Haskell/Meta/Syntax/Translate.hs
--- old/haskell-src-meta-0.7.0.1/src/Language/Haskell/Meta/Syntax/Translate.hs
2017-01-11 14:37:22.000000000 +0100
+++ new/haskell-src-meta-0.8.0.1/src/Language/Haskell/Meta/Syntax/Translate.hs
2017-05-31 20:40:48.000000000 +0200
@@ -42,11 +42,20 @@
class ToTyVars a where toTyVars :: a -> [TyVarBndr]
#if MIN_VERSION_haskell_src_exts(1,18,0)
class ToMaybeKind a where toMaybeKind :: a -> Maybe Kind
+#endif
#if MIN_VERSION_template_haskell(2,11,0)
class ToInjectivityAnn a where toInjectivityAnn :: a -> InjectivityAnn
#endif
+
+#if MIN_VERSION_template_haskell(2,12,0)
+#elif MIN_VERSION_template_haskell(2,11,0)
+type DerivClause = Pred
+#else
+type DerivClause = Name
#endif
+class ToDerivClauses a where toDerivClauses :: a -> [DerivClause]
+
-- for error messages
moduleName = "Language.Haskell.Meta.Syntax.Translate"
@@ -342,7 +351,6 @@
toStrictType :: Hs.Type l -> StrictType
-#if MIN_VERSION_haskell_src_exts(1,18,0)
#if MIN_VERSION_template_haskell(2,11,0)
toStrictType (Hs.TyBang _ s u t) = (Bang (toUnpack u) (toStrict s), toType t)
where
@@ -353,7 +361,7 @@
toUnpack (Hs.NoUnpack _) = SourceNoUnpack
toUnpack (Hs.NoUnpackPragma _) = NoSourceUnpackedness
toStrictType x = (Bang NoSourceUnpackedness NoSourceStrictness, toType x)
-#else
+#elif MIN_VERSION_haskell_src_exts(1,18,0)
-- TyBang l (BangType l) (Unpackedness l) (Type l)
-- data BangType l = BangedTy l | LazyTy l | NoStrictAnnot l
-- data Unpackedness l = Unpack l | NoUnpack l | NoUnpackPragma l
@@ -364,25 +372,12 @@
toStrict _ (Hs.Unpack _) = Unpacked
toStrict _ _ = NotStrict
toStrictType x = (NotStrict, toType x)
-#endif
#else
-#if MIN_VERSION_template_haskell(2,11,0)
-toStrictType (Hs.TyBang _ (Hs.UnpackedTy _) t) = toStrictType2 SourceUnpack t
-toStrictType t = toStrictType2 NoSourceUnpackedness t
-
-toStrictType2 u t@(Hs.TyBang _ _ Hs.TyBang{}) =
- nonsense "toStrictType" "double strictness annotation" t
-toStrictType2 u (Hs.TyBang _ (Hs.BangedTy _) t) = (Bang u SourceStrict, toType
t)
-toStrictType2 u (Hs.TyBang _ (Hs.UnpackedTy _) t) =
- nonsense "toStrictType" "double unpackedness annotation" t
-toStrictType2 u t = (Bang u NoSourceStrictness, toType t)
-#else /* !MIN_VERSION_template_haskell(2,11,0) */
toStrictType t@(Hs.TyBang _ _ Hs.TyBang{}) =
nonsense "toStrictType" "double strictness annotation" t
toStrictType (Hs.TyBang _ (Hs.BangedTy _) t) = (IsStrict, toType t)
toStrictType (Hs.TyBang _ (Hs.UnpackedTy _) t) = (Unpacked, toType t)
toStrictType t = (NotStrict, toType t)
-#endif /* !MIN_VERSION_template_haskell(2,11,0) */
#endif
@@ -402,16 +397,20 @@
toPred [email protected]{} = noTH "toCxt" a
toPred p = todo "toPred" p
-#if MIN_VERSION_template_haskell(2,11,0)
-instance ToCxt (Hs.Deriving l) where
- toCxt (Hs.Deriving _ rule) = toCxt rule
-instance ToCxt [Hs.InstRule l] where
- toCxt = concatMap toCxt
+#if MIN_VERSION_template_haskell(2,12,0)
+instance ToDerivClauses (Hs.Deriving l) where
+ toDerivClauses (Hs.Deriving _ irules) = [DerivClause Nothing (map toType
irules)]
+#elif MIN_VERSION_template_haskell(2,11,0)
+instance ToDerivClauses (Hs.Deriving l) where
+ toDerivClauses (Hs.Deriving _ irules) = map toType irules
+#else
+instance ToDerivClauses (Hs.Deriving l) where
+ toDerivClauses (Hs.Deriving _ irules) = concatMap toNames irules
#endif
-instance ToCxt a => ToCxt (Maybe a) where
- toCxt Nothing = []
- toCxt (Just a) = toCxt a
+instance ToDerivClauses a => ToDerivClauses (Maybe a) where
+ toDerivClauses Nothing = []
+ toDerivClauses (Just a) = toDerivClauses a
foldAppT :: Type -> [Type] -> Type
foldAppT t ts = foldl' AppT t ts
@@ -444,13 +443,7 @@
Nothing
#endif
(fmap qualConDeclToCon qcds)
-#if MIN_VERSION_template_haskell(2,11,0)
- -- Convert a Deriving into a list of types, one
for each derived class
- -- Assumes that the types do not have any contexts
- (maybe [] (\(Hs.Deriving _ q) -> map toType q)
qns)
-#else
- (toNames qns)
-#endif
+ (toDerivClauses qns)
Hs.NewType _ -> let qcd = case qcds of
[x] -> x
_ -> nonsense "toDec" ("newtype with "
++
@@ -462,11 +455,7 @@
Nothing
#endif
(qualConDeclToCon qcd)
-#if MIN_VERSION_template_haskell(2,11,0)
- (maybe [] (\(Hs.Deriving _ q) -> map
toType q) qns)
-#else
- (toNames qns)
-#endif
+ (toDerivClauses qns)
-- This type-signature conversion is just wrong.
-- Type variables need to be dealt with. /Jonas
@@ -483,7 +472,6 @@
inline | b = Inline | otherwise = NoInline
#if MIN_VERSION_template_haskell(2,11,0)
-#if MIN_VERSION_haskell_src_exts(1,18,0)
toDec (Hs.TypeFamDecl _ h sig inj)
= OpenTypeFamilyD $ TypeFamilyHead (toName h)
(toTyVars h)
@@ -491,19 +479,7 @@
(fmap toInjectivityAnn inj)
toDec (Hs.DataFamDecl _ _ h sig)
= DataFamilyD (toName h) (toTyVars h) (toMaybeKind sig)
-#else
- toDec (Hs.TypeFamDecl _ h k)
- = OpenTypeFamilyD $ TypeFamilyHead (toName h)
- (toTyVars h)
- (maybe NoSig (KindSig . toKind) k)
- Nothing
- -- TODO: do something with context?
- toDec (Hs.DataFamDecl _ _ h k)
- = DataFamilyD (toName h) (toTyVars h) (fmap toKind k)
-#endif
-
-#else
-#if MIN_VERSION_haskell_src_exts(1,18,0)
+#elif MIN_VERSION_haskell_src_exts(1,18,0)
toDec (Hs.TypeFamDecl _ h sig inj)
= FamilyD TypeFam (toName h) (toTyVars h) (toMaybeKind sig)
toDec (Hs.DataFamDecl _ _ h sig)
@@ -516,7 +492,6 @@
toDec (Hs.DataFamDecl _ _ h k)
= FamilyD DataFam (toName h) (toTyVars h) (fmap toKind k)
#endif
-#endif /* MIN_VERSION_template_haskell(2,11,0) */
toDec a@(Hs.FunBind _ mtchs) = hsMatchesToFunD
mtchs
toDec (Hs.PatBind _ p rhs bnds) = ValD (toPat p)
@@ -561,12 +536,12 @@
instance ToMaybeKind a => ToMaybeKind (Maybe a) where
toMaybeKind Nothing = Nothing
toMaybeKind (Just a) = toMaybeKind a
+#endif
#if MIN_VERSION_template_haskell(2,11,0)
instance ToInjectivityAnn (Hs.InjectivityInfo l) where
toInjectivityAnn (Hs.InjectivityInfo _ n ns) = InjectivityAnn (toName n)
(fmap toName ns)
#endif
-#endif
transAct :: Maybe (Hs.Activation l) -> Phases
transAct Nothing = AllPhases
@@ -610,6 +585,10 @@
Hs.CxSingle _ x' -> [toPred x']
Hs.CxTuple _ xs -> fmap toPred xs
+instance ToCxt a => ToCxt (Maybe a) where
+ toCxt Nothing = []
+ toCxt (Just a) = toCxt a
+
instance ToType (Hs.InstRule l) where
toType (Hs.IRule _ _ _ h) = toType h
toType (Hs.IParen _ irule) = toType irule
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore'
old/haskell-src-meta-0.7.0.1/src/Language/Haskell/TH/Instances/Lift.hs
new/haskell-src-meta-0.8.0.1/src/Language/Haskell/TH/Instances/Lift.hs
--- old/haskell-src-meta-0.7.0.1/src/Language/Haskell/TH/Instances/Lift.hs
2017-01-11 14:37:22.000000000 +0100
+++ new/haskell-src-meta-0.8.0.1/src/Language/Haskell/TH/Instances/Lift.hs
1970-01-01 01:00:00.000000000 +0100
@@ -1,16 +0,0 @@
-{- |
- Module : Language.Haskell.TH.Instances.Lift
- Copyright : (c) Matt Morrow 2008
- License : BSD3
- Maintainer : Matt Morrow <[email protected]>
- Stability : experimental
- Portability : portable (template-haskell)
-
- This module is exported for backwards-compatibility purposes.
- All it does is re-export the instances defined in
- "Language.Haskell.TH.Instances", from the th-orphans package.
--}
-module Language.Haskell.TH.Instances.Lift
- {-# DEPRECATED "Use the th-orphans package instead." #-} () where
-
-import Language.Haskell.TH.Instances
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn'
'--exclude=.svnignore' old/haskell-src-meta-0.7.0.1/tests/Main.hs
new/haskell-src-meta-0.8.0.1/tests/Main.hs
--- old/haskell-src-meta-0.7.0.1/tests/Main.hs 1970-01-01 01:00:00.000000000
+0100
+++ new/haskell-src-meta-0.8.0.1/tests/Main.hs 2017-05-31 20:40:48.000000000
+0200
@@ -0,0 +1,33 @@
+{-# LANGUAGE CPP #-}
+
+module Main where
+
+import Language.Haskell.Meta.Parse
+#if MIN_VERSION_haskell_src_exts(1,18,0)
+import qualified Language.Haskell.Exts as Exts
+#else
+import qualified Language.Haskell.Exts.Annotated as Exts
+#endif
+import qualified Language.Haskell.TH as TH
+import Test.Framework
+import Test.Framework.Providers.HUnit
+import Test.HUnit (Assertion, (@?=))
+
+main :: IO ()
+main = defaultMain tests
+
+tests :: [Test]
+tests = [derivingClausesTest]
+
+derivingClausesTest :: Test
+derivingClausesTest = testCase "Deriving clauses preserved" $
+ roundTripDecls "data Foo = Foo deriving (A, B, C)"
+
+roundTripDecls :: String -> Assertion
+roundTripDecls s = do
+ declsExts <- liftEither $ parseHsDecls s
+ declsExts' <- liftEither $ parseDecs s >>= parseHsDecls . TH.pprint
+ declsExts' @?= declsExts
+
+liftEither :: Monad m => Either String a -> m a
+liftEither = either fail return