Skip to content

Commit

Permalink
Use nats package to provided Natural instances with old bases
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Mar 1, 2016
1 parent 692d3dd commit fb299ae
Show file tree
Hide file tree
Showing 4 changed files with 20 additions and 4 deletions.
4 changes: 1 addition & 3 deletions Data/Aeson/Types/Instances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,7 @@ import Data.Word (Word8, Word16, Word32, Word64)
import Data.Version (Version, showVersion, parseVersion)
import Text.ParserCombinators.ReadP (readP_to_S)
import Foreign.Storable (Storable)
import Numeric.Natural (Natural)
import Prelude hiding (foldr)
import qualified Data.Aeson.Encode.Builder as E
import qualified Data.Aeson.Parser.Time as Time
Expand All @@ -111,7 +112,6 @@ import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU

#if MIN_VERSION_base(4,8,0)
import Numeric.Natural
#else
import Control.Applicative ((<$>), (<*>), pure)
import Data.Monoid (mempty)
Expand Down Expand Up @@ -353,7 +353,6 @@ instance FromJSON Integer where
parseJSON = withScientific "Integral" $ pure . truncate
{-# INLINE parseJSON #-}

#if MIN_VERSION_base(4,8,0)
instance ToJSON Natural where
toJSON = toJSON . toInteger
{-# INLINE toJSON #-}
Expand All @@ -366,7 +365,6 @@ instance FromJSON Natural where
if Scientific.coefficient s < 0
then fail $ "Expected a Natural number but got the negative number: " <> show s
else pure $ truncate s
#endif

instance ToJSON Int8 where
toJSON = Number . fromIntegral
Expand Down
9 changes: 8 additions & 1 deletion aeson.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -107,9 +107,13 @@ library
vector >= 0.7.1

if !impl(ghc >= 8.0)
-- `Data.Semigroup` is available in base only since GHC 8.0
-- `Data.Semigroup` is available in base only since GHC 8.0 / base 4.9
build-depends: semigroups >= 0.16.1

if !impl(ghc >= 7.10)
-- `Numeric.Natural` is available in base only since GHC 7.10 / base 4.8
build-depends: nats >=1 && <1.1

if flag(old-locale)
build-depends: time < 1.5, old-locale
else
Expand Down Expand Up @@ -167,6 +171,9 @@ test-suite tests
else
build-depends: time >= 1.5

if !impl(ghc >= 7.10)
build-depends: nats >=1 && <1.1

source-repository head
type: git
location: git://github.com/bos/aeson.git
Expand Down
9 changes: 9 additions & 0 deletions tests/Instances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,10 @@ import Functions

import Test.QuickCheck.Instances ()

#if !MIN_VERSION_base(4,8,0) && !MIN_VERSION_QuickCheck(2,8,3)
import Numeric.Natural
#endif

-- "System" types.

instance Arbitrary DotNetTime where
Expand Down Expand Up @@ -145,3 +149,8 @@ instance Arbitrary Version where
makeVersion :: [Int] -> Version
makeVersion b = Version b []
#endif

#if !MIN_VERSION_base(4,8,0) && !MIN_VERSION_QuickCheck(2,8,3)
instance Arbitrary Natural where
arbitrary = fromInteger . abs <$> arbitrary
#endif
2 changes: 2 additions & 0 deletions tests/Properties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ import Data.Int (Int8)
import Data.Time (Day, LocalTime, NominalDiffTime, TimeOfDay, UTCTime,
ZonedTime)
import Data.Version (Version)
import Numeric.Natural (Natural)
import Encoders
import Instances ()
import Test.Framework (Test, testGroup)
Expand Down Expand Up @@ -139,6 +140,7 @@ tests = testGroup "properties" [
, testProperty "ZonedTime" $ roundTripEq (undefined :: ZonedTime)
, testProperty "NominalDiffTime" $ roundTripEq (undefined :: NominalDiffTime)
, testProperty "Version" $ roundTripEq (undefined :: Version)
, testProperty "Natural" $ roundTripEq (undefined :: Natural)
, testGroup "ghcGenerics" [
testProperty "OneConstructor" $ roundTripEq OneConstructor
, testProperty "Product2" $ roundTripEq (undefined :: Product2 Int Bool)
Expand Down

0 comments on commit fb299ae

Please sign in to comment.