[DHG_packages] 01/01: haskell-aeson: cherry-pick upstream testsuite fix

Gianfranco Costamagna locutusofborg at moszumanska.debian.org
Tue Jul 18 16:21:58 UTC 2017


This is an automated email from the git hooks/post-receive script.

locutusofborg pushed a commit to branch master
in repository DHG_packages.

commit 873477a309ad4abce7b8d058f596e8e087d131a3
Author: Gianfranco Costamagna <costamagnagianfranco at yahoo.it>
Date:   Tue Jul 18 18:21:25 2017 +0200

    haskell-aeson: cherry-pick upstream testsuite fix
---
 p/haskell-aeson/debian/changelog                 |   6 +
 p/haskell-aeson/debian/patches/32bit-fixes.patch | 294 +++++++++++++++++++++++
 p/haskell-aeson/debian/patches/series            |   1 +
 3 files changed, 301 insertions(+)

diff --git a/p/haskell-aeson/debian/changelog b/p/haskell-aeson/debian/changelog
index 27f69ba..10e39da 100644
--- a/p/haskell-aeson/debian/changelog
+++ b/p/haskell-aeson/debian/changelog
@@ -1,3 +1,9 @@
+haskell-aeson (1.0.2.1-6) unstable; urgency=medium
+
+  * Fix BE and 32bit builds.
+
+ -- Gianfranco Costamagna <locutusofborg at debian.org>  Tue, 18 Jul 2017 17:22:07 +0200
+
 haskell-aeson (1.0.2.1-5) unstable; urgency=medium
 
   [ Adrian Bunk <bunk at debian.org> ]
diff --git a/p/haskell-aeson/debian/patches/32bit-fixes.patch b/p/haskell-aeson/debian/patches/32bit-fixes.patch
new file mode 100644
index 0000000..4d659c9
--- /dev/null
+++ b/p/haskell-aeson/debian/patches/32bit-fixes.patch
@@ -0,0 +1,294 @@
+Origin: https://github.com/bos/aeson/pull/569 https://github.com/bos/aeson/issues/568
+Description: this should fix the testsuite issues in 32 bit architectures and big endian ones
+--- haskell-aeson-1.0.2.1.orig/tests/UnitTests.hs
++++ haskell-aeson-1.0.2.1/tests/UnitTests.hs
+@@ -29,6 +29,7 @@ import Data.Aeson.Text (encodeToTextBuil
+ import Data.Aeson.Types (Options(..), SumEncoding(..), ToJSON(..), Value, camelTo, camelTo2, defaultOptions, omitNothingFields)
+ import Data.Char (toUpper)
+ import Data.Fixed (Pico)
++import Data.Foldable (for_, toList)
+ import Data.Functor.Compose (Compose(..))
+ import Data.Functor.Identity (Identity(..))
+ import Data.Functor.Product (Product(..))
+@@ -280,34 +281,49 @@ dotColonMark = [
+ data Example where
+     Example
+         :: (Eq a, Show a, ToJSON a, FromJSON a)
+-        => String -> L.ByteString -> a -> Example
++        => String -> [L.ByteString] -> a -> Example -- empty bytestring will fail, any p [] == False
+     MaybeExample
+         :: (Eq a, Show a, FromJSON a)
+         => String -> L.ByteString -> Maybe a -> Example
+ 
++
++example :: (Eq a, Show a, ToJSON a, FromJSON a)
++        => String -> L.ByteString -> a -> Example
++example n bs x = Example n [bs] x 
++
+ assertJsonExample :: Example -> Test
+-assertJsonExample (Example name bs val) = testCase name $ do
+-    assertEqual "encode"           bs         (encode val)
+-    assertEqual "encode/via value" bs         (encode $ toJSON val)
+-    assertEqual "decode"           (Just val) (decode bs)
++assertJsonExample (Example name bss val) = testCase name $ do
++    assertSomeEqual "encode"           bss        (encode val)
++    assertSomeEqual "encode/via value" bss        (encode $ toJSON val)
++    for_ bss $ \bs ->
++        assertEqual "decode"           (Just val) (decode bs)
+ assertJsonExample (MaybeExample name bs mval) = testCase name $
+     assertEqual "decode" mval (decode bs)
+ 
+ assertJsonEncodingExample :: Example -> Test
+-assertJsonEncodingExample (Example name bs val) = testCase name $ do
+-    assertEqual "encode"           bs (encode val)
+-    assertEqual "encode/via value" bs (encode $ toJSON val)
++assertJsonEncodingExample (Example name bss val) = testCase name $ do
++    assertSomeEqual "encode"           bss (encode val)
++    assertSomeEqual "encode/via value" bss (encode $ toJSON val)
+ assertJsonEncodingExample (MaybeExample name _ _) = testCase name $
+     assertFailure "cannot encode MaybeExample"
+ 
++
++assertSomeEqual :: (Eq a, Show a, Foldable f) => String -> f a -> a -> IO ()
++assertSomeEqual preface expected actual
++    | elem actual expected = return ()
++    | otherwise = assertFailure $ preface
++        ++ ": expecting one of " ++ show (toList expected)
++        ++ ", got " ++ show actual
++
++
+ jsonEncodingExamples :: [Example]
+ jsonEncodingExamples =
+   [
+   -- Maybe serialising is lossy
+   -- https://github.com/bos/aeson/issues/376
+-    Example "Just Nothing" "null" (Just Nothing :: Maybe (Maybe Int))
++    example "Just Nothing" "null" (Just Nothing :: Maybe (Maybe Int))
+   -- infinities cannot be recovered, null is decoded as NaN
+-  , Example "inf :: Double" "null" (Approx $ 1/0 :: Approx Double)
++  , example "inf :: Double" "null" (Approx $ 1/0 :: Approx Double)
+   ]
+ 
+ jsonDecodingExamples :: [Example]
+@@ -329,113 +345,125 @@ jsonDecodingExamples = [
+ jsonExamples :: [Example]
+ jsonExamples =
+   [
+-    Example "Either Left" "{\"Left\":1}"  (Left 1 :: Either Int Int)
+-  , Example "Either Right" "{\"Right\":1}"  (Right 1 :: Either Int Int)
+-  , Example "Nothing"  "null"  (Nothing :: Maybe Int)
+-  , Example "Just"  "1"  (Just 1 :: Maybe Int)
+-  , Example "Proxy Int" "null"  (Proxy :: Proxy Int)
+-  , Example "Tagged Char Int" "1"  (Tagged 1 :: Tagged Char Int)
++    example "Either Left" "{\"Left\":1}"  (Left 1 :: Either Int Int)
++  , example "Either Right" "{\"Right\":1}"  (Right 1 :: Either Int Int)
++  , example "Nothing"  "null"  (Nothing :: Maybe Int)
++  , example "Just"  "1"  (Just 1 :: Maybe Int)
++  , example "Proxy Int" "null"  (Proxy :: Proxy Int)
++  , example "Tagged Char Int" "1"  (Tagged 1 :: Tagged Char Int)
+ #if __GLASGOW_HASKELL__ >= 708
+     -- Test Tagged instance is polykinded
+-  , Example "Tagged 123 Int" "1"  (Tagged 1 :: Tagged 123 Int)
++  , example "Tagged 123 Int" "1"  (Tagged 1 :: Tagged 123 Int)
+ #endif
+-  , Example "Const Char Int" "\"c\""  (Const 'c' :: Const Char Int)
+-  , Example "Tuple" "[1,2]"  ((1, 2) :: (Int, Int))
+-  , Example "NonEmpty" "[1,2,3]"  (1 :| [2, 3] :: NonEmpty Int)
+-  , Example "Seq" "[1,2,3]"  (Seq.fromList [1, 2, 3] ::  Seq.Seq Int)
+-  , Example "DList" "[1,2,3]"  (DList.fromList [1, 2, 3] :: DList.DList Int)
+-  , Example "()" "[]"  ()
+-
+-  , Example "HashMap Int Int"          "{\"0\":1,\"2\":3}"  (HM.fromList [(0,1),(2,3)] :: HM.HashMap Int Int)
+-  , Example "Map Int Int"              "{\"0\":1,\"2\":3}"  (M.fromList [(0,1),(2,3)] :: M.Map Int Int)
+-  , Example "Map (Tagged Int Int) Int" "{\"0\":1,\"2\":3}"  (M.fromList [(Tagged 0,1),(Tagged 2,3)] :: M.Map (Tagged Int Int) Int)
+-  , Example "Map [Int] Int"            "[[[0],1],[[2],3]]"  (M.fromList [([0],1),([2],3)] :: M.Map [Int] Int)
+-  , Example "Map [Char] Int"           "{\"ab\":1,\"cd\":3}"  (M.fromList [("ab",1),("cd",3)] :: M.Map [Char] Int)
+-  , Example "Map [I Char] Int"         "{\"ab\":1,\"cd\":3}"  (M.fromList [(map pure "ab",1),(map pure "cd",3)] :: M.Map [I Char] Int)
+-
+-  , Example "nan :: Double" "null"  (Approx $ 0/0 :: Approx Double)
+-
+-  , Example "Ordering LT" "\"LT\"" LT
+-  , Example "Ordering EQ" "\"EQ\"" EQ
+-  , Example "Ordering GT" "\"GT\"" GT
+-
+-  , Example "Float" "3.14" (3.14 :: Float)
+-  , Example "Pico" "3.14" (3.14 :: Pico)
+-  , Example "Scientific" "3.14" (3.14 :: Scientific)
+-
+-  , Example "Set Int" "[1,2,3]" (Set.fromList [3, 2, 1] :: Set.Set Int)
+-  , Example "IntSet"  "[1,2,3]" (IntSet.fromList [3, 2, 1])
+-  , Example "IntMap" "[[1,2],[3,4]]" (IntMap.fromList [(3,4), (1,2)] :: IntMap.IntMap Int)
+-  , Example "Vector" "[1,2,3]" (Vector.fromList [1, 2, 3] :: Vector.Vector Int)
+-  , Example "HashSet Int" "[1,2,3]" (HashSet.fromList [3, 2, 1] :: HashSet.HashSet Int)
+-  , Example "Tree Int" "[1,[[2,[[3,[]],[4,[]]]],[5,[]]]]" (let n = Tree.Node in n 1 [n 2 [n 3 [], n 4 []], n 5 []] :: Tree.Tree Int)
++  , example "Const Char Int" "\"c\""  (Const 'c' :: Const Char Int)
++  , example "Tuple" "[1,2]"  ((1, 2) :: (Int, Int))
++  , example "NonEmpty" "[1,2,3]"  (1 :| [2, 3] :: NonEmpty Int)
++  , example "Seq" "[1,2,3]"  (Seq.fromList [1, 2, 3] ::  Seq.Seq Int)
++  , example "DList" "[1,2,3]"  (DList.fromList [1, 2, 3] :: DList.DList Int)
++  , example "()" "[]"  ()
++
++  , Example "HashMap Int Int"
++        [ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"]
++        (HM.fromList [(0,1),(2,3)] :: HM.HashMap Int Int)
++  , Example "Map Int Int"
++        [ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"]
++        (M.fromList [(0,1),(2,3)] :: M.Map Int Int)
++  , Example "Map (Tagged Int Int) Int"
++        [ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"]
++        (M.fromList [(Tagged 0,1),(Tagged 2,3)] :: M.Map (Tagged Int Int) Int)
++  , example "Map [Int] Int"
++        "[[[0],1],[[2],3]]"
++        (M.fromList [([0],1),([2],3)] :: M.Map [Int] Int)
++  , Example "Map [Char] Int"
++        [ "{\"ab\":1,\"cd\":3}", "{\"cd\":3,\"ab\":1}" ]
++        (M.fromList [("ab",1),("cd",3)] :: M.Map String Int)
++  , Example "Map [I Char] Int"
++        [ "{\"ab\":1,\"cd\":3}", "{\"cd\":3,\"ab\":1}" ]
++        (M.fromList [(map pure "ab",1),(map pure "cd",3)] :: M.Map [I Char] Int)
++
++  , example "nan :: Double" "null"  (Approx $ 0/0 :: Approx Double)
++
++  , example "Ordering LT" "\"LT\"" LT
++  , example "Ordering EQ" "\"EQ\"" EQ
++  , example "Ordering GT" "\"GT\"" GT
++
++  , example "Float" "3.14" (3.14 :: Float)
++  , example "Pico" "3.14" (3.14 :: Pico)
++  , example "Scientific" "3.14" (3.14 :: Scientific)
++
++  , example "Set Int" "[1,2,3]" (Set.fromList [3, 2, 1] :: Set.Set Int)
++  , example "IntSet"  "[1,2,3]" (IntSet.fromList [3, 2, 1])
++  , example "IntMap" "[[1,2],[3,4]]" (IntMap.fromList [(3,4), (1,2)] :: IntMap.IntMap Int)
++  , example "Vector" "[1,2,3]" (Vector.fromList [1, 2, 3] :: Vector.Vector Int)
++  , example "HashSet Int" "[1,2,3]" (HashSet.fromList [3, 2, 1] :: HashSet.HashSet Int)
++  , example "Tree Int" "[1,[[2,[[3,[]],[4,[]]]],[5,[]]]]" (let n = Tree.Node in n 1 [n 2 [n 3 [], n 4 []], n 5 []] :: Tree.Tree Int)
+ 
+   -- Three separate cases, as ordering in HashMap is not defined
+-  , Example "HashMap Float Int, NaN" "{\"NaN\":1}"  (Approx $ HM.singleton (0/0) 1 :: Approx (HM.HashMap Float Int))
+-  , Example "HashMap Float Int, Infinity" "{\"Infinity\":1}"  (HM.singleton (1/0) 1 :: HM.HashMap Float Int)
+-  , Example "HashMap Float Int, +Infinity" "{\"-Infinity\":1}"  (HM.singleton (negate 1/0) 1 :: HM.HashMap Float Int)
++  , example "HashMap Float Int, NaN" "{\"NaN\":1}"  (Approx $ HM.singleton (0/0) 1 :: Approx (HM.HashMap Float Int))
++  , example "HashMap Float Int, Infinity" "{\"Infinity\":1}"  (HM.singleton (1/0) 1 :: HM.HashMap Float Int)
++  , example "HashMap Float Int, +Infinity" "{\"-Infinity\":1}"  (HM.singleton (negate 1/0) 1 :: HM.HashMap Float Int)
+ 
+   -- Functors
+-  , Example "Identity Int" "1"  (pure 1 :: Identity Int)
++  , example "Identity Int" "1"  (pure 1 :: Identity Int)
+ 
+-  , Example "Identity Char" "\"x\""      (pure 'x' :: Identity Char)
+-  , Example "Identity String" "\"foo\""  (pure "foo" :: Identity String)
+-  , Example "[Identity Char]" "\"xy\""   ([pure 'x', pure 'y'] :: [Identity Char])
+-
+-  , Example "Maybe Char" "\"x\""              (pure 'x' :: Maybe Char)
+-  , Example "Maybe String" "\"foo\""          (pure "foo" :: Maybe String)
+-  , Example "Maybe [Identity Char]" "\"xy\""  (pure [pure 'x', pure 'y'] :: Maybe [Identity Char])
+-
+-  , Example "Product I Maybe Int" "[1,2]"         (Pair (pure 1) (pure 2) :: Product I Maybe Int)
+-  , Example "Product I Maybe Int" "[1,null]"      (Pair (pure 1) Nothing :: Product I Maybe Int)
+-  , Example "Product I [] Char" "[\"a\",\"foo\"]" (Pair (pure 'a') "foo" :: Product I [] Char)
+-
+-  , Example "Sum I [] Int: InL"  "{\"InL\":1}"       (InL (pure 1) :: Sum I [] Int)
+-  , Example "Sum I [] Int: InR"  "{\"InR\":[1,2]}"   (InR [1, 2] :: Sum I [] Int)
+-  , Example "Sum I [] Char: InR" "{\"InR\":\"foo\"}" (InR "foo" :: Sum I [] Char)
+-
+-  , Example "Compose I  I  Int" "1"      (pure 1 :: Compose I I   Int)
+-  , Example "Compose I  [] Int" "[1]"    (pure 1 :: Compose I []  Int)
+-  , Example "Compose [] I  Int" "[1]"    (pure 1 :: Compose [] I  Int)
+-  , Example "Compose [] [] Int" "[[1]]"  (pure 1 :: Compose [] [] Int)
+-
+-  , Example "Compose I  I  Char" "\"x\""    (pure 'x' :: Compose I  I  Char)
+-  , Example "Compose I  [] Char" "\"x\""    (pure 'x' :: Compose I  [] Char)
+-  , Example "Compose [] I  Char" "\"x\""    (pure 'x' :: Compose [] I  Char)
+-  , Example "Compose [] [] Char" "[\"x\"]"  (pure 'x' :: Compose [] [] Char)
+-
+-  , Example "Compose3 I  I  I  Char" "\"x\""      (pure 'x' :: Compose3 I  I  I  Char)
+-  , Example "Compose3 I  I  [] Char" "\"x\""      (pure 'x' :: Compose3 I  I  [] Char)
+-  , Example "Compose3 I  [] I  Char" "\"x\""      (pure 'x' :: Compose3 I  [] I  Char)
+-  , Example "Compose3 I  [] [] Char" "[\"x\"]"    (pure 'x' :: Compose3 I  [] [] Char)
+-  , Example "Compose3 [] I  I  Char" "\"x\""      (pure 'x' :: Compose3 [] I  I  Char)
+-  , Example "Compose3 [] I  [] Char" "[\"x\"]"    (pure 'x' :: Compose3 [] I  [] Char)
+-  , Example "Compose3 [] [] I  Char" "[\"x\"]"    (pure 'x' :: Compose3 [] [] I  Char)
+-  , Example "Compose3 [] [] [] Char" "[[\"x\"]]"  (pure 'x' :: Compose3 [] [] [] Char)
+-
+-  , Example "Compose3' I  I  I  Char" "\"x\""      (pure 'x' :: Compose3' I  I  I  Char)
+-  , Example "Compose3' I  I  [] Char" "\"x\""      (pure 'x' :: Compose3' I  I  [] Char)
+-  , Example "Compose3' I  [] I  Char" "\"x\""      (pure 'x' :: Compose3' I  [] I  Char)
+-  , Example "Compose3' I  [] [] Char" "[\"x\"]"    (pure 'x' :: Compose3' I  [] [] Char)
+-  , Example "Compose3' [] I  I  Char" "\"x\""      (pure 'x' :: Compose3' [] I  I  Char)
+-  , Example "Compose3' [] I  [] Char" "[\"x\"]"    (pure 'x' :: Compose3' [] I  [] Char)
+-  , Example "Compose3' [] [] I  Char" "[\"x\"]"    (pure 'x' :: Compose3' [] [] I  Char)
+-  , Example "Compose3' [] [] [] Char" "[[\"x\"]]"  (pure 'x' :: Compose3' [] [] [] Char)
++  , example "Identity Char" "\"x\""      (pure 'x' :: Identity Char)
++  , example "Identity String" "\"foo\""  (pure "foo" :: Identity String)
++  , example "[Identity Char]" "\"xy\""   ([pure 'x', pure 'y'] :: [Identity Char])
++
++  , example "Maybe Char" "\"x\""              (pure 'x' :: Maybe Char)
++  , example "Maybe String" "\"foo\""          (pure "foo" :: Maybe String)
++  , example "Maybe [Identity Char]" "\"xy\""  (pure [pure 'x', pure 'y'] :: Maybe [Identity Char])
++
++  , example "Product I Maybe Int" "[1,2]"         (Pair (pure 1) (pure 2) :: Product I Maybe Int)
++  , example "Product I Maybe Int" "[1,null]"      (Pair (pure 1) Nothing :: Product I Maybe Int)
++  , example "Product I [] Char" "[\"a\",\"foo\"]" (Pair (pure 'a') "foo" :: Product I [] Char)
++
++  , example "Sum I [] Int: InL"  "{\"InL\":1}"       (InL (pure 1) :: Sum I [] Int)
++  , example "Sum I [] Int: InR"  "{\"InR\":[1,2]}"   (InR [1, 2] :: Sum I [] Int)
++  , example "Sum I [] Char: InR" "{\"InR\":\"foo\"}" (InR "foo" :: Sum I [] Char)
++
++  , example "Compose I  I  Int" "1"      (pure 1 :: Compose I I   Int)
++  , example "Compose I  [] Int" "[1]"    (pure 1 :: Compose I []  Int)
++  , example "Compose [] I  Int" "[1]"    (pure 1 :: Compose [] I  Int)
++  , example "Compose [] [] Int" "[[1]]"  (pure 1 :: Compose [] [] Int)
++
++  , example "Compose I  I  Char" "\"x\""    (pure 'x' :: Compose I  I  Char)
++  , example "Compose I  [] Char" "\"x\""    (pure 'x' :: Compose I  [] Char)
++  , example "Compose [] I  Char" "\"x\""    (pure 'x' :: Compose [] I  Char)
++  , example "Compose [] [] Char" "[\"x\"]"  (pure 'x' :: Compose [] [] Char)
++
++  , example "Compose3 I  I  I  Char" "\"x\""      (pure 'x' :: Compose3 I  I  I  Char)
++  , example "Compose3 I  I  [] Char" "\"x\""      (pure 'x' :: Compose3 I  I  [] Char)
++  , example "Compose3 I  [] I  Char" "\"x\""      (pure 'x' :: Compose3 I  [] I  Char)
++  , example "Compose3 I  [] [] Char" "[\"x\"]"    (pure 'x' :: Compose3 I  [] [] Char)
++  , example "Compose3 [] I  I  Char" "\"x\""      (pure 'x' :: Compose3 [] I  I  Char)
++  , example "Compose3 [] I  [] Char" "[\"x\"]"    (pure 'x' :: Compose3 [] I  [] Char)
++  , example "Compose3 [] [] I  Char" "[\"x\"]"    (pure 'x' :: Compose3 [] [] I  Char)
++  , example "Compose3 [] [] [] Char" "[[\"x\"]]"  (pure 'x' :: Compose3 [] [] [] Char)
++
++  , example "Compose3' I  I  I  Char" "\"x\""      (pure 'x' :: Compose3' I  I  I  Char)
++  , example "Compose3' I  I  [] Char" "\"x\""      (pure 'x' :: Compose3' I  I  [] Char)
++  , example "Compose3' I  [] I  Char" "\"x\""      (pure 'x' :: Compose3' I  [] I  Char)
++  , example "Compose3' I  [] [] Char" "[\"x\"]"    (pure 'x' :: Compose3' I  [] [] Char)
++  , example "Compose3' [] I  I  Char" "\"x\""      (pure 'x' :: Compose3' [] I  I  Char)
++  , example "Compose3' [] I  [] Char" "[\"x\"]"    (pure 'x' :: Compose3' [] I  [] Char)
++  , example "Compose3' [] [] I  Char" "[\"x\"]"    (pure 'x' :: Compose3' [] [] I  Char)
++  , example "Compose3' [] [] [] Char" "[[\"x\"]]"  (pure 'x' :: Compose3' [] [] [] Char)
+ 
+-  , Example "MyEither Int String: Left"  "42"      (MyLeft 42     :: MyEither Int String)
+-  , Example "MyEither Int String: Right" "\"foo\"" (MyRight "foo" :: MyEither Int String)
++  , example "MyEither Int String: Left"  "42"      (MyLeft 42     :: MyEither Int String)
++  , example "MyEither Int String: Right" "\"foo\"" (MyRight "foo" :: MyEither Int String)
+ 
+   -- newtypes from Monoid/Semigroup
+-  , Example "Monoid.Dual Int" "2" (pure 2 :: Monoid.Dual Int)
+-  , Example "Monoid.First Int" "2" (pure 2 :: Monoid.First Int)
+-  , Example "Monoid.Last Int" "2" (pure 2 :: Monoid.Last Int)
+-  , Example "Semigroup.Min Int" "2" (pure 2 :: Semigroup.Min Int)
+-  , Example "Semigroup.Max Int" "2" (pure 2 :: Semigroup.Max Int)
+-  , Example "Semigroup.First Int" "2" (pure 2 :: Semigroup.First Int)
+-  , Example "Semigroup.Last Int" "2" (pure 2 :: Semigroup.Last Int)
+-  , Example "Semigroup.WrappedMonoid Int" "2" (Semigroup.WrapMonoid 2 :: Semigroup.WrappedMonoid Int)
+-  , Example "Semigroup.Option Just" "2" (pure 2 :: Semigroup.Option Int)
+-  , Example "Semigroup.Option Nothing" "null" (Semigroup.Option (Nothing :: Maybe Bool))
++  , example "Monoid.Dual Int" "2" (pure 2 :: Monoid.Dual Int)
++  , example "Monoid.First Int" "2" (pure 2 :: Monoid.First Int)
++  , example "Monoid.Last Int" "2" (pure 2 :: Monoid.Last Int)
++  , example "Semigroup.Min Int" "2" (pure 2 :: Semigroup.Min Int)
++  , example "Semigroup.Max Int" "2" (pure 2 :: Semigroup.Max Int)
++  , example "Semigroup.First Int" "2" (pure 2 :: Semigroup.First Int)
++  , example "Semigroup.Last Int" "2" (pure 2 :: Semigroup.Last Int)
++  , example "Semigroup.WrappedMonoid Int" "2" (Semigroup.WrapMonoid 2 :: Semigroup.WrappedMonoid Int)
++  , example "Semigroup.Option Just" "2" (pure 2 :: Semigroup.Option Int)
++  , example "Semigroup.Option Nothing" "null" (Semigroup.Option (Nothing :: Maybe Bool))
+   ]
+ 
+ 
diff --git a/p/haskell-aeson/debian/patches/series b/p/haskell-aeson/debian/patches/series
index 79ecbcd..9c9756a 100644
--- a/p/haskell-aeson/debian/patches/series
+++ b/p/haskell-aeson/debian/patches/series
@@ -1,2 +1,3 @@
 th-option.diff
 threaded-option.diff
+32bit-fixes.patch

-- 
Alioth's /usr/local/bin/git-commit-notice on /srv/git.debian.org/git/pkg-haskell/DHG_packages.git



More information about the Pkg-haskell-commits mailing list