#ifdef GENERICS
#endif
module Data.Aeson.Types.Instances
(
FromJSON(..)
, ToJSON(..)
#ifdef GENERICS
, GFromJSON(..)
, GToJSON(..)
, genericToJSON
, genericParseJSON
#endif
, DotNetTime(..)
, withObject
, withText
, withArray
, withNumber
, withScientific
, withBool
, fromJSON
, (.:)
, (.:?)
, (.!=)
, (.=)
, typeMismatch
) where
import Control.Applicative ((<$>), (<*>), (<|>), pure, empty)
import Data.Aeson.Functions
import Data.Aeson.Types.Class
import Data.Aeson.Types.Internal
import Data.Scientific (Scientific)
import qualified Data.Scientific as Scientific (coefficient, base10Exponent, fromFloatDigits, toRealFloat)
import Data.Attoparsec.Number (Number(..))
import Data.Fixed
import Data.Hashable (Hashable(..))
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Maybe (fromMaybe)
import Data.Monoid (Dual(..), First(..), Last(..), mappend)
import Data.Ratio (Ratio, (%), numerator, denominator)
import Data.Text (Text, pack, unpack)
import Data.Time (UTCTime, ZonedTime(..), TimeZone(..))
import Data.Time.Format (FormatTime, formatTime, parseTime)
import Data.Traversable (traverse)
import Data.Vector (Vector)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Foreign.Storable (Storable)
import System.Locale (defaultTimeLocale, dateTimeFmt)
import qualified Data.HashMap.Strict as H
import qualified Data.HashSet as HashSet
import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.Map as M
import qualified Data.Set as Set
import qualified Data.Tree as Tree
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import qualified Data.Vector as V
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Mutable as VM ( unsafeNew, unsafeWrite )
instance (ToJSON a) => ToJSON (Maybe a) where
toJSON (Just a) = toJSON a
toJSON Nothing = Null
instance (FromJSON a) => FromJSON (Maybe a) where
parseJSON Null = pure Nothing
parseJSON a = Just <$> parseJSON a
instance (ToJSON a, ToJSON b) => ToJSON (Either a b) where
toJSON (Left a) = object [left .= a]
toJSON (Right b) = object [right .= b]
instance (FromJSON a, FromJSON b) => FromJSON (Either a b) where
parseJSON (Object (H.toList -> [(key, value)]))
| key == left = Left <$> parseJSON value
| key == right = Right <$> parseJSON value
parseJSON _ = fail $
"expected an object with a single property " ++
"where the property key should be either " ++
"\"Left\" or \"Right\""
left, right :: Text
left = "Left"
right = "Right"
instance ToJSON Bool where
toJSON = Bool
instance FromJSON Bool where
parseJSON = withBool "Bool" pure
instance ToJSON () where
toJSON _ = emptyArray
instance FromJSON () where
parseJSON = withArray "()" $ \v ->
if V.null v
then pure ()
else fail "Expected an empty array"
instance ToJSON [Char] where
toJSON = String . T.pack
instance FromJSON [Char] where
parseJSON = withText "String" $ pure . T.unpack
instance ToJSON Char where
toJSON = String . T.singleton
instance FromJSON Char where
parseJSON = withText "Char" $ \t ->
if T.compareLength t 1 == EQ
then pure $ T.head t
else fail "Expected a string of length 1"
instance ToJSON Scientific where
toJSON = Number
instance FromJSON Scientific where
parseJSON = withScientific "Scientific" pure
instance ToJSON Double where
toJSON = realFloatToJSON
instance FromJSON Double where
parseJSON = parseRealFloat "Double"
instance ToJSON Number where
toJSON (D d) = toJSON d
toJSON (I i) = toJSON i
instance FromJSON Number where
parseJSON (Number s) = pure $ scientificToNumber s
parseJSON Null = pure (D (0/0))
parseJSON v = typeMismatch "Number" v
instance ToJSON Float where
toJSON = realFloatToJSON
instance FromJSON Float where
parseJSON = parseRealFloat "Float"
instance ToJSON (Ratio Integer) where
toJSON r = object [ "numerator" .= numerator r
, "denominator" .= denominator r
]
instance FromJSON (Ratio Integer) where
parseJSON = withObject "Rational" $ \obj ->
(%) <$> obj .: "numerator"
<*> obj .: "denominator"
instance HasResolution a => ToJSON (Fixed a) where
toJSON = Number . realToFrac
instance HasResolution a => FromJSON (Fixed a) where
parseJSON = withScientific "Fixed" $ pure . realToFrac
instance ToJSON Int where
toJSON = Number . fromIntegral
instance FromJSON Int where
parseJSON = parseIntegral "Int"
instance ToJSON Integer where
toJSON = Number . fromInteger
instance FromJSON Integer where
parseJSON = withScientific "Integral" $ pure . floor
instance ToJSON Int8 where
toJSON = Number . fromIntegral
instance FromJSON Int8 where
parseJSON = parseIntegral "Int8"
instance ToJSON Int16 where
toJSON = Number . fromIntegral
instance FromJSON Int16 where
parseJSON = parseIntegral "Int16"
instance ToJSON Int32 where
toJSON = Number . fromIntegral
instance FromJSON Int32 where
parseJSON = parseIntegral "Int32"
instance ToJSON Int64 where
toJSON = Number . fromIntegral
instance FromJSON Int64 where
parseJSON = parseIntegral "Int64"
instance ToJSON Word where
toJSON = Number . fromIntegral
instance FromJSON Word where
parseJSON = parseIntegral "Word"
instance ToJSON Word8 where
toJSON = Number . fromIntegral
instance FromJSON Word8 where
parseJSON = parseIntegral "Word8"
instance ToJSON Word16 where
toJSON = Number . fromIntegral
instance FromJSON Word16 where
parseJSON = parseIntegral "Word16"
instance ToJSON Word32 where
toJSON = Number . fromIntegral
instance FromJSON Word32 where
parseJSON = parseIntegral "Word32"
instance ToJSON Word64 where
toJSON = Number . fromIntegral
instance FromJSON Word64 where
parseJSON = parseIntegral "Word64"
instance ToJSON Text where
toJSON = String
instance FromJSON Text where
parseJSON = withText "Text" pure
instance ToJSON LT.Text where
toJSON = String . LT.toStrict
instance FromJSON LT.Text where
parseJSON = withText "Lazy Text" $ pure . LT.fromStrict
instance (ToJSON a) => ToJSON [a] where
toJSON = Array . V.fromList . map toJSON
instance (FromJSON a) => FromJSON [a] where
parseJSON = withArray "[a]" $ mapM parseJSON . V.toList
instance (ToJSON a) => ToJSON (Vector a) where
toJSON = Array . V.map toJSON
instance (FromJSON a) => FromJSON (Vector a) where
parseJSON = withArray "Vector a" $ V.mapM parseJSON
vectorToJSON :: (VG.Vector v a, ToJSON a) => v a -> Value
vectorToJSON = Array . V.map toJSON . V.convert
vectorParseJSON :: (FromJSON a, VG.Vector w a) => String -> Value -> Parser (w a)
vectorParseJSON s = withArray s $ fmap V.convert . V.mapM parseJSON
instance (Storable a, ToJSON a) => ToJSON (VS.Vector a) where
toJSON = vectorToJSON
instance (Storable a, FromJSON a) => FromJSON (VS.Vector a) where
parseJSON = vectorParseJSON "Data.Vector.Storable.Vector a"
instance (VP.Prim a, ToJSON a) => ToJSON (VP.Vector a) where
toJSON = vectorToJSON
instance (VP.Prim a, FromJSON a) => FromJSON (VP.Vector a) where
parseJSON = vectorParseJSON "Data.Vector.Primitive.Vector a"
instance (VG.Vector VU.Vector a, ToJSON a) => ToJSON (VU.Vector a) where
toJSON = vectorToJSON
instance (VG.Vector VU.Vector a, FromJSON a) => FromJSON (VU.Vector a) where
parseJSON = vectorParseJSON "Data.Vector.Unboxed.Vector a"
instance (ToJSON a) => ToJSON (Set.Set a) where
toJSON = toJSON . Set.toList
instance (Ord a, FromJSON a) => FromJSON (Set.Set a) where
parseJSON = fmap Set.fromList . parseJSON
instance (ToJSON a) => ToJSON (HashSet.HashSet a) where
toJSON = toJSON . HashSet.toList
instance (Eq a, Hashable a, FromJSON a) => FromJSON (HashSet.HashSet a) where
parseJSON = fmap HashSet.fromList . parseJSON
instance ToJSON IntSet.IntSet where
toJSON = toJSON . IntSet.toList
instance FromJSON IntSet.IntSet where
parseJSON = fmap IntSet.fromList . parseJSON
instance ToJSON a => ToJSON (IntMap.IntMap a) where
toJSON = toJSON . IntMap.toList
instance FromJSON a => FromJSON (IntMap.IntMap a) where
parseJSON = fmap IntMap.fromList . parseJSON
instance (ToJSON v) => ToJSON (M.Map Text v) where
toJSON = Object . M.foldrWithKey (\k -> H.insert k . toJSON) H.empty
instance (FromJSON v) => FromJSON (M.Map Text v) where
parseJSON = withObject "Map Text a" $
fmap (H.foldrWithKey M.insert M.empty) . traverse parseJSON
instance (ToJSON v) => ToJSON (M.Map LT.Text v) where
toJSON = Object . mapHashKeyVal LT.toStrict toJSON
instance (FromJSON v) => FromJSON (M.Map LT.Text v) where
parseJSON = fmap (hashMapKey LT.fromStrict) . parseJSON
instance (ToJSON v) => ToJSON (M.Map String v) where
toJSON = Object . mapHashKeyVal pack toJSON
instance (FromJSON v) => FromJSON (M.Map String v) where
parseJSON = fmap (hashMapKey unpack) . parseJSON
instance (ToJSON v) => ToJSON (H.HashMap Text v) where
toJSON = Object . H.map toJSON
instance (FromJSON v) => FromJSON (H.HashMap Text v) where
parseJSON = withObject "HashMap Text a" $ traverse parseJSON
instance (ToJSON v) => ToJSON (H.HashMap LT.Text v) where
toJSON = Object . mapKeyVal LT.toStrict toJSON
instance (FromJSON v) => FromJSON (H.HashMap LT.Text v) where
parseJSON = fmap (mapKey LT.fromStrict) . parseJSON
instance (ToJSON v) => ToJSON (H.HashMap String v) where
toJSON = Object . mapKeyVal pack toJSON
instance (FromJSON v) => FromJSON (H.HashMap String v) where
parseJSON = fmap (mapKey unpack) . parseJSON
instance (ToJSON v) => ToJSON (Tree.Tree v) where
toJSON (Tree.Node root branches) = toJSON (root,branches)
instance (FromJSON v) => FromJSON (Tree.Tree v) where
parseJSON j = uncurry Tree.Node <$> parseJSON j
instance ToJSON Value where
toJSON a = a
instance FromJSON Value where
parseJSON a = pure a
instance ToJSON DotNetTime where
toJSON (DotNetTime t) =
String (pack (secs ++ formatMillis t ++ ")/"))
where secs = formatTime defaultTimeLocale "/Date(%s" t
instance FromJSON DotNetTime where
parseJSON = withText "DotNetTime" $ \t ->
let (s,m) = T.splitAt (T.length t 5) t
t' = T.concat [s,".",m]
in case parseTime defaultTimeLocale "/Date(%s%Q)/" (unpack t') of
Just d -> pure (DotNetTime d)
_ -> fail "could not parse .NET time"
instance ToJSON ZonedTime where
toJSON t = String $ pack $ formatTime defaultTimeLocale format t
where
format = "%FT%T." ++ formatMillis t ++ tzFormat
tzFormat
| 0 == timeZoneMinutes (zonedTimeZone t) = "Z"
| otherwise = "%z"
formatMillis :: (FormatTime t) => t -> String
formatMillis t = take 3 . formatTime defaultTimeLocale "%q" $ t
instance FromJSON ZonedTime where
parseJSON (String t) =
tryFormats alternateFormats
<|> fail "could not parse ECMA-262 ISO-8601 date"
where
tryFormat f =
case parseTime defaultTimeLocale f (unpack t) of
Just d -> pure d
Nothing -> empty
tryFormats = foldr1 (<|>) . map tryFormat
alternateFormats =
dateTimeFmt defaultTimeLocale :
distributeList ["%Y", "%Y-%m", "%F"]
["T%R", "T%T", "T%T%Q", "T%T%QZ", "T%T%Q%z"]
distributeList xs ys =
foldr (\x acc -> acc ++ distribute x ys) [] xs
distribute x = map (mappend x)
parseJSON v = typeMismatch "ZonedTime" v
instance ToJSON UTCTime where
toJSON t = String (pack (take 23 str ++ "Z"))
where str = formatTime defaultTimeLocale "%FT%T.%q" t
instance FromJSON UTCTime where
parseJSON = withText "UTCTime" $ \t ->
case parseTime defaultTimeLocale "%FT%T%QZ" (unpack t) of
Just d -> pure d
_ -> fail "could not parse ISO-8601 date"
instance (ToJSON a, ToJSON b) => ToJSON (a,b) where
toJSON (a,b) = Array $ V.create $ do
mv <- VM.unsafeNew 2
VM.unsafeWrite mv 0 (toJSON a)
VM.unsafeWrite mv 1 (toJSON b)
return mv
instance (FromJSON a, FromJSON b) => FromJSON (a,b) where
parseJSON = withArray "(a,b)" $ \ab ->
let n = V.length ab
in if n == 2
then (,) <$> parseJSON (V.unsafeIndex ab 0)
<*> parseJSON (V.unsafeIndex ab 1)
else fail $ "cannot unpack array of length " ++
show n ++ " into a pair"
instance (ToJSON a, ToJSON b, ToJSON c) => ToJSON (a,b,c) where
toJSON (a,b,c) = Array $ V.create $ do
mv <- VM.unsafeNew 3
VM.unsafeWrite mv 0 (toJSON a)
VM.unsafeWrite mv 1 (toJSON b)
VM.unsafeWrite mv 2 (toJSON c)
return mv
instance (FromJSON a, FromJSON b, FromJSON c) => FromJSON (a,b,c) where
parseJSON = withArray "(a,b,c)" $ \abc ->
let n = V.length abc
in if n == 3
then (,,) <$> parseJSON (V.unsafeIndex abc 0)
<*> parseJSON (V.unsafeIndex abc 1)
<*> parseJSON (V.unsafeIndex abc 2)
else fail $ "cannot unpack array of length " ++
show n ++ " into a 3-tuple"
instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a,b,c,d) where
toJSON (a,b,c,d) = Array $ V.create $ do
mv <- VM.unsafeNew 4
VM.unsafeWrite mv 0 (toJSON a)
VM.unsafeWrite mv 1 (toJSON b)
VM.unsafeWrite mv 2 (toJSON c)
VM.unsafeWrite mv 3 (toJSON d)
return mv
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a,b,c,d) where
parseJSON = withArray "(a,b,c,d)" $ \abcd ->
let n = V.length abcd
in if n == 4
then (,,,) <$> parseJSON (V.unsafeIndex abcd 0)
<*> parseJSON (V.unsafeIndex abcd 1)
<*> parseJSON (V.unsafeIndex abcd 2)
<*> parseJSON (V.unsafeIndex abcd 3)
else fail $ "cannot unpack array of length " ++
show n ++ " into a 4-tuple"
instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a,b,c,d,e) where
toJSON (a,b,c,d,e) = Array $ V.create $ do
mv <- VM.unsafeNew 5
VM.unsafeWrite mv 0 (toJSON a)
VM.unsafeWrite mv 1 (toJSON b)
VM.unsafeWrite mv 2 (toJSON c)
VM.unsafeWrite mv 3 (toJSON d)
VM.unsafeWrite mv 4 (toJSON e)
return mv
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a,b,c,d,e) where
parseJSON = withArray "(a,b,c,d,e)" $ \abcde ->
let n = V.length abcde
in if n == 5
then (,,,,) <$> parseJSON (V.unsafeIndex abcde 0)
<*> parseJSON (V.unsafeIndex abcde 1)
<*> parseJSON (V.unsafeIndex abcde 2)
<*> parseJSON (V.unsafeIndex abcde 3)
<*> parseJSON (V.unsafeIndex abcde 4)
else fail $ "cannot unpack array of length " ++
show n ++ " into a 5-tuple"
instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a,b,c,d,e,f) where
toJSON (a,b,c,d,e,f) = Array $ V.create $ do
mv <- VM.unsafeNew 6
VM.unsafeWrite mv 0 (toJSON a)
VM.unsafeWrite mv 1 (toJSON b)
VM.unsafeWrite mv 2 (toJSON c)
VM.unsafeWrite mv 3 (toJSON d)
VM.unsafeWrite mv 4 (toJSON e)
VM.unsafeWrite mv 5 (toJSON f)
return mv
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a,b,c,d,e,f) where
parseJSON = withArray "(a,b,c,d,e,f)" $ \abcdef ->
let n = V.length abcdef
in if n == 6
then (,,,,,) <$> parseJSON (V.unsafeIndex abcdef 0)
<*> parseJSON (V.unsafeIndex abcdef 1)
<*> parseJSON (V.unsafeIndex abcdef 2)
<*> parseJSON (V.unsafeIndex abcdef 3)
<*> parseJSON (V.unsafeIndex abcdef 4)
<*> parseJSON (V.unsafeIndex abcdef 5)
else fail $ "cannot unpack array of length " ++
show n ++ " into a 6-tuple"
instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a,b,c,d,e,f,g) where
toJSON (a,b,c,d,e,f,g) = Array $ V.create $ do
mv <- VM.unsafeNew 7
VM.unsafeWrite mv 0 (toJSON a)
VM.unsafeWrite mv 1 (toJSON b)
VM.unsafeWrite mv 2 (toJSON c)
VM.unsafeWrite mv 3 (toJSON d)
VM.unsafeWrite mv 4 (toJSON e)
VM.unsafeWrite mv 5 (toJSON f)
VM.unsafeWrite mv 6 (toJSON g)
return mv
instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a,b,c,d,e,f,g) where
parseJSON = withArray "(a,b,c,d,e,f,g)" $ \abcdefg ->
let n = V.length abcdefg
in if n == 7
then (,,,,,,) <$> parseJSON (V.unsafeIndex abcdefg 0)
<*> parseJSON (V.unsafeIndex abcdefg 1)
<*> parseJSON (V.unsafeIndex abcdefg 2)
<*> parseJSON (V.unsafeIndex abcdefg 3)
<*> parseJSON (V.unsafeIndex abcdefg 4)
<*> parseJSON (V.unsafeIndex abcdefg 5)
<*> parseJSON (V.unsafeIndex abcdefg 6)
else fail $ "cannot unpack array of length " ++
show n ++ " into a 7-tuple"
instance ToJSON a => ToJSON (Dual a) where
toJSON = toJSON . getDual
instance FromJSON a => FromJSON (Dual a) where
parseJSON = fmap Dual . parseJSON
instance ToJSON a => ToJSON (First a) where
toJSON = toJSON . getFirst
instance FromJSON a => FromJSON (First a) where
parseJSON = fmap First . parseJSON
instance ToJSON a => ToJSON (Last a) where
toJSON = toJSON . getLast
instance FromJSON a => FromJSON (Last a) where
parseJSON = fmap Last . parseJSON
withObject :: String -> (Object -> Parser a) -> Value -> Parser a
withObject _ f (Object obj) = f obj
withObject expected _ v = typeMismatch expected v
withText :: String -> (Text -> Parser a) -> Value -> Parser a
withText _ f (String txt) = f txt
withText expected _ v = typeMismatch expected v
withArray :: String -> (Array -> Parser a) -> Value -> Parser a
withArray _ f (Array arr) = f arr
withArray expected _ v = typeMismatch expected v
withNumber :: String -> (Number -> Parser a) -> Value -> Parser a
withNumber expected f = withScientific expected (f . scientificToNumber)
withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a
withScientific _ f (Number scientific) = f scientific
withScientific expected _ v = typeMismatch expected v
withBool :: String -> (Bool -> Parser a) -> Value -> Parser a
withBool _ f (Bool arr) = f arr
withBool expected _ v = typeMismatch expected v
(.=) :: ToJSON a => Text -> a -> Pair
name .= value = (name, toJSON value)
fromJSON :: (FromJSON a) => Value -> Result a
fromJSON = parse parseJSON
(.:) :: (FromJSON a) => Object -> Text -> Parser a
obj .: key = case H.lookup key obj of
Nothing -> fail $ "key " ++ show key ++ " not present"
Just v -> parseJSON v
(.:?) :: (FromJSON a) => Object -> Text -> Parser (Maybe a)
obj .:? key = case H.lookup key obj of
Nothing -> pure Nothing
Just v -> parseJSON v
(.!=) :: Parser (Maybe a) -> a -> Parser a
pmval .!= val = fromMaybe val <$> pmval
typeMismatch :: String
-> Value
-> Parser a
typeMismatch expected actual =
fail $ "when expecting a " ++ expected ++ ", encountered " ++ name ++
" instead"
where
name = case actual of
Object _ -> "Object"
Array _ -> "Array"
String _ -> "String"
Number _ -> "Number"
Bool _ -> "Boolean"
Null -> "Null"
realFloatToJSON :: RealFloat a => a -> Value
realFloatToJSON d
| isNaN d || isInfinite d = Null
| otherwise = Number $ Scientific.fromFloatDigits d
scientificToNumber :: Scientific -> Number
scientificToNumber s
| e < 0 = D $ Scientific.toRealFloat s
| otherwise = I $ c * 10 ^ e
where
e = Scientific.base10Exponent s
c = Scientific.coefficient s
parseRealFloat :: RealFloat a => String -> Value -> Parser a
parseRealFloat _ (Number s) = pure $ Scientific.toRealFloat s
parseRealFloat _ Null = pure (0/0)
parseRealFloat expected v = typeMismatch expected v
parseIntegral :: Integral a => String -> Value -> Parser a
parseIntegral expected = withScientific expected $ pure . floor