Hello community, here is the log from the commit of package ghc-json for openSUSE:Factory checked in at 2018-12-28 12:35:09 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/ghc-json (Old) and /work/SRC/openSUSE:Factory/.ghc-json.new.28833 (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Package is "ghc-json" Fri Dec 28 12:35:09 2018 rev:7 rq:661495 version:0.9.3 Changes: -------- --- /work/SRC/openSUSE:Factory/ghc-json/ghc-json.changes 2018-10-25 08:26:55.695785941 +0200 +++ /work/SRC/openSUSE:Factory/.ghc-json.new.28833/ghc-json.changes 2018-12-28 12:35:23.859960303 +0100 @@ -1,0 +2,7 @@ +Fri Dec 21 03:02:49 UTC 2018 - psimons@suse.com + +- Update json to version 0.9.3. + Upstream has not updated the file "CHANGES" since the last + release. + +------------------------------------------------------------------- Old: ---- json-0.9.2.tar.gz New: ---- json-0.9.3.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ ghc-json.spec ++++++ --- /var/tmp/diff_new_pack.boG8PP/_old 2018-12-28 12:35:24.407959920 +0100 +++ /var/tmp/diff_new_pack.boG8PP/_new 2018-12-28 12:35:24.411959918 +0100 @@ -18,7 +18,7 @@ %global pkg_name json Name: ghc-%{pkg_name} -Version: 0.9.2 +Version: 0.9.3 Release: 0 Summary: Support for serialising Haskell to and from JSON License: BSD-3-Clause ++++++ json-0.9.2.tar.gz -> json-0.9.3.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/json-0.9.2/Text/JSON/Generic.hs new/json-0.9.3/Text/JSON/Generic.hs --- old/json-0.9.2/Text/JSON/Generic.hs 2018-03-17 20:49:55.000000000 +0100 +++ new/json-0.9.3/Text/JSON/Generic.hs 2001-09-09 03:46:40.000000000 +0200 @@ -1,15 +1,5 @@ {-# LANGUAGE PatternGuards #-} --------------------------------------------------------------------- --- | --- Module : Text.JSON.Generic --- Copyright : (c) Lennart Augustsson, 2008-2009 --- License : BSD3 --- --- Maintainer: Sigbjorn Finne <sof@galois.com> --- Stability : provisional --- Portability: portable --- --- JSON serializer and deserializer using Data.Generics. +-- | JSON serializer and deserializer using Data.Generics. -- The functions here handle algebraic data types and primitive types. -- It uses the same representation as "Text.JSON" for "Prelude" types. module Text.JSON.Generic @@ -107,7 +97,7 @@ mungeField ('_':cs) = cs mungeField cs = cs - jsObject :: [(String, JSValue)] -> JSValue + jsObject :: [(String, JSValue)] -> JSValue jsObject = JSObject . toJSObject @@ -117,7 +107,7 @@ fromJSON :: (Data a) => JSValue -> Result a fromJSON j = fromJSON_generic j `ext1R` jList - -- + `extR` (value :: F Integer) `extR` (value :: F Int) `extR` (value :: F Word8) @@ -132,11 +122,11 @@ `extR` (value :: F Float) `extR` (value :: F Char) `extR` (value :: F String) - -- + `extR` (value :: F Bool) `extR` (value :: F ()) `extR` (value :: F Ordering) - -- + `extR` (value :: F I.IntSet) `extR` (value :: F S.ByteString) `extR` (value :: F L.ByteString) @@ -162,9 +152,9 @@ getConstr t (JSObject o) | [(s, j')] <- fromJSObject o = do c <- readConstr' t s; return (c, j') getConstr t (JSString js) = do c <- readConstr' t (fromJSString js); return (c, JSNull) -- handle nullare constructor getConstr _ _ = Error "fromJSON: bad constructor encoding" - readConstr' t s = - maybe (Error $ "fromJSON: unknown constructor: " ++ s ++ " " ++ show t) - return $ readConstr t s + readConstr' t s = + maybe (Error $ "fromJSON: unknown constructor: " ++ s ++ " " ++ show t) + return $ readConstr t s decodeArgs c = decodeArgs' (numConstrArgs (resType generic) c) c (constrFields c) decodeArgs' 0 c _ JSNull = construct c [] -- nullary constructor diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/json-0.9.2/Text/JSON/Parsec.hs new/json-0.9.3/Text/JSON/Parsec.hs --- old/json-0.9.2/Text/JSON/Parsec.hs 2018-03-17 20:49:55.000000000 +0100 +++ new/json-0.9.3/Text/JSON/Parsec.hs 2001-09-09 03:46:40.000000000 +0200 @@ -1,13 +1,4 @@ --------------------------------------------------------------------- --- | --- Module : Text.JSON.Parsec --- Copyright : (c) Galois, Inc. 2007-2009 --- --- Maintainer: Sigbjorn Finne <sof@galois.com> --- Stability : provisional --- Portability: portable --- --- Parse JSON values using the Parsec combinators. +-- | Parse JSON values using the Parsec combinators. module Text.JSON.Parsec ( p_value diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/json-0.9.2/Text/JSON/Pretty.hs new/json-0.9.3/Text/JSON/Pretty.hs --- old/json-0.9.2/Text/JSON/Pretty.hs 2018-03-17 20:49:55.000000000 +0100 +++ new/json-0.9.3/Text/JSON/Pretty.hs 2001-09-09 03:46:40.000000000 +0200 @@ -1,14 +1,4 @@ --------------------------------------------------------------------- --- | --- Module : Text.JSON.Pretty --- Copyright : (c) Galois, Inc. 2007-2009 --- License : BSD3 --- --- Maintainer: Sigbjorn Finne <sof@galois.com> --- Stability : provisional --- Portability: portable --- --- Display JSON values using pretty printing combinators. +-- | Display JSON values using pretty printing combinators. module Text.JSON.Pretty ( module Text.JSON.Pretty @@ -50,7 +40,7 @@ pp_string x = doubleQuotes $ hcat $ map pp_char x where pp_char '\\' = text "\\\\" pp_char '"' = text "\\\"" - pp_char c | isControl c || fromEnum c >= 0x7f = uni_esc c + pp_char c | isControl c = uni_esc c pp_char c = char c uni_esc c = text "\\u" PP.<> text (pad 4 (showHex (fromEnum c) "")) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/json-0.9.2/Text/JSON/ReadP.hs new/json-0.9.3/Text/JSON/ReadP.hs --- old/json-0.9.2/Text/JSON/ReadP.hs 2018-03-17 20:49:55.000000000 +0100 +++ new/json-0.9.3/Text/JSON/ReadP.hs 2001-09-09 03:46:40.000000000 +0200 @@ -1,14 +1,4 @@ --------------------------------------------------------------------- --- | --- Module : Text.JSON.ReadP --- Copyright : (c) Galois, Inc. 2007-2009 --- License : BSD3 --- --- Maintainer: Sigbjorn Finne <sof@galois.com> --- Stability : provisional --- Portability: portable --- --- Parse JSON values using the ReadP combinators. +-- | Parse JSON values using the ReadP combinators. module Text.JSON.ReadP ( p_value diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/json-0.9.2/Text/JSON/String.hs new/json-0.9.3/Text/JSON/String.hs --- old/json-0.9.2/Text/JSON/String.hs 2018-03-17 20:49:55.000000000 +0100 +++ new/json-0.9.3/Text/JSON/String.hs 2001-09-09 03:46:40.000000000 +0200 @@ -1,17 +1,4 @@ --------------------------------------------------------------------- --- | --- Module : Text.JSON.String --- Copyright : (c) Galois, Inc. 2007-2009 --- License : BSD3 --- --- Maintainer: Sigbjorn Finne <sof@galois.com> --- Stability : provisional --- Portability: portable --- --------------------------------------------------------------------- --- --- Basic support for working with JSON values. --- +-- | Basic support for working with JSON values. module Text.JSON.String ( @@ -173,12 +160,12 @@ '0' -> frac 0 cs _ | not (isDigit c) -> fail $ "Unable to parse JSON Rational: " ++ context cs - | otherwise -> readDigits (digitToIntI c) cs + | otherwise -> readDigits (digitToIntI c) cs readDigits acc [] = frac (fromInteger acc) [] readDigits acc (x:xs) | isDigit x = let acc' = 10*acc + digitToIntI x in - acc' `seq` readDigits acc' xs + acc' `seq` readDigits acc' xs | otherwise = frac (fromInteger acc) (x:xs) frac n ('.' : ds) = diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/json-0.9.2/Text/JSON/Types.hs new/json-0.9.3/Text/JSON/Types.hs --- old/json-0.9.2/Text/JSON/Types.hs 2018-03-17 20:49:55.000000000 +0100 +++ new/json-0.9.3/Text/JSON/Types.hs 2001-09-09 03:46:40.000000000 +0200 @@ -1,18 +1,5 @@ {-# LANGUAGE DeriveDataTypeable #-} --------------------------------------------------------------------- --- | --- Module : Text.JSON.Types --- Copyright : (c) Galois, Inc. 2007-2009 --- License : BSD3 --- --- Maintainer: Sigbjorn Finne <sof@galois.com> --- Stability : provisional --- Portability: portable --- --------------------------------------------------------------------- --- --- Basic support for working with JSON values. --- +-- | Basic support for working with JSON values. module Text.JSON.Types ( @@ -32,6 +19,7 @@ ) where import Data.Typeable ( Typeable ) +import Data.String(IsString(..)) -- -- | JSON values @@ -72,6 +60,12 @@ toJSString = JSONString -- Note: we don't encode the string yet, that's done when serializing. +instance IsString JSString where + fromString = toJSString + +instance IsString JSValue where + fromString = JSString . fromString + -- | As can association lists newtype JSObject e = JSONObject { fromJSObject :: [(String, e)] } deriving (Eq, Ord, Show, Read, Typeable ) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/json-0.9.2/Text/JSON.hs new/json-0.9.3/Text/JSON.hs --- old/json-0.9.2/Text/JSON.hs 2018-03-17 20:49:55.000000000 +0100 +++ new/json-0.9.3/Text/JSON.hs 2001-09-09 03:46:40.000000000 +0200 @@ -1,19 +1,5 @@ {-# LANGUAGE CPP, TypeSynonymInstances, FlexibleInstances #-} --------------------------------------------------------------------- --- | --- Module : Text.JSON --- Copyright : (c) Galois, Inc. 2007-2009 --- License : BSD3 --- --- Maintainer: Sigbjorn Finne <sof@galois.com> --- Stability : provisional --- Portability: portable --- --------------------------------------------------------------------- --- --- Serialising Haskell values to and from JSON values. --- - +-- | Serialising Haskell values to and from JSON values. module Text.JSON ( -- * JSON Types JSValue(..) @@ -216,9 +202,9 @@ readOrd x = case x of "LT" -> return Prelude.LT - "EQ" -> return Prelude.EQ - "GT" -> return Prelude.GT - _ -> mkError ("Unable to read Ordering") + "EQ" -> return Prelude.EQ + "GT" -> return Prelude.GT + _ -> mkError ("Unable to read Ordering") -- ----------------------------------------------------------------- -- Integral types @@ -399,16 +385,14 @@ arrayFromList :: (Array.Ix i) => [(i,e)] -> Array.Array i e arrayFromList [] = Array.array undefined [] arrayFromList ls@((i,_):xs) = Array.array bnds ls - where - bnds = - foldr (\ (ix,_) (mi,ma) -> - let - mi1 = min ix mi - ma1 = max ix ma - in - mi1 `seq` ma1 `seq` (mi1,ma1)) - (i,i) - xs + where + bnds = foldr step (i,i) xs + + step (ix,_) (mi,ma) = + let mi1 = min ix mi + ma1 = max ix ma + in mi1 `seq` ma1 `seq` (mi1,ma1) + -- ----------------------------------------------------------------- -- ByteStrings @@ -440,7 +424,7 @@ valFromObj :: JSON a => String -> JSObject JSValue -> Result a valFromObj k o = maybe (Error $ "valFromObj: Could not find key: " ++ show k) readJSON - (lookup k (fromJSObject o)) + (lookup k (fromJSObject o)) encJSString :: (a -> String) -> a -> JSValue encJSString f v = JSString (toJSString (f v)) @@ -484,8 +468,8 @@ -- | Decode a 'JSObject' value into an association list. decJSDict :: (JSKey a, JSON b) => String - -> JSValue - -> Result [(a,b)] + -> JSValue + -> Result [(a,b)] decJSDict l (JSObject o) = mapM rd (fromJSObject o) where rd (a,b) = case fromJSKey a of Just pa -> readJSON b >>= \pb -> return (pa,pb) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/json-0.9.2/json.cabal new/json-0.9.3/json.cabal --- old/json-0.9.2/json.cabal 2018-03-17 20:49:55.000000000 +0100 +++ new/json-0.9.3/json.cabal 2001-09-09 03:46:40.000000000 +0200 @@ -1,5 +1,5 @@ name: json -version: 0.9.2 +version: 0.9.3 synopsis: Support for serialising Haskell to and from JSON description: JSON (JavaScript Object Notation) is a lightweight data-interchange @@ -15,7 +15,7 @@ license-file: LICENSE author: Galois Inc. maintainer: Iavor S. Diatchki (iavor.diatchki@gmail.com) -Copyright: (c) 2007-2009 Galois Inc. +Copyright: (c) 2007-2018 Galois Inc. cabal-version: >= 1.6 build-type: Simple extra-source-files: @@ -114,3 +114,6 @@ if flag(mapdict) cpp-options: -DMAP_AS_DICT + + +