@@ -2,7 +2,8 @@ module Data.Argonaut.Decode.Decoders where
22
33import Prelude
44
5- import Data.Argonaut.Core (Json , caseJsonBoolean , caseJsonNull , caseJsonNumber , caseJsonString , isNull , stringify , toArray , toObject , toString )
5+ import Data.Argonaut.Core (Json , caseJsonBoolean , caseJsonNull , caseJsonNumber , caseJsonString , isNull , toArray , toObject , toString , fromString )
6+ import Data.Argonaut.Decode.Errors (JsonDecodeError (..))
67import Data.Array as Arr
78import Data.Array.NonEmpty (NonEmptyArray )
89import Data.Array.NonEmpty as NEA
@@ -24,125 +25,125 @@ import Data.TraversableWithIndex (traverseWithIndex)
2425import Data.Tuple (Tuple (..))
2526import Foreign.Object as FO
2627
27- decodeIdentity :: ∀ a . (Json -> Either String a ) -> Json -> Either String (Identity a )
28+ decodeIdentity :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (Identity a )
2829decodeIdentity decoder j = Identity <$> decoder j
2930
30- decodeMaybe :: ∀ a . (Json -> Either String a ) -> Json -> Either String (Maybe a )
31+ decodeMaybe :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (Maybe a )
3132decodeMaybe decoder j
3233 | isNull j = pure Nothing
3334 | otherwise = Just <$> decoder j
3435
35- decodeTuple :: ∀ a b . (Json -> Either String a ) -> (Json -> Either String b ) -> Json -> Either String (Tuple a b )
36+ decodeTuple :: ∀ a b . (Json -> Either JsonDecodeError a ) -> (Json -> Either JsonDecodeError b ) -> Json -> Either JsonDecodeError (Tuple a b )
3637decodeTuple decoderA decoderB j = decodeArray Right j >>= f
3738 where
38- f :: Array Json -> Either String (Tuple a b )
39+ f :: Array Json -> Either JsonDecodeError (Tuple a b )
3940 f [a, b] = Tuple <$> decoderA a <*> decoderB b
40- f _ = Left " Couldn't decode Tuple"
41+ f _ = Left $ TypeMismatch " Tuple"
4142
42- decodeEither :: ∀ a b . (Json -> Either String a ) -> (Json -> Either String b ) -> Json -> Either String (Either a b )
43+ decodeEither :: ∀ a b . (Json -> Either JsonDecodeError a ) -> (Json -> Either JsonDecodeError b ) -> Json -> Either JsonDecodeError (Either a b )
4344decodeEither decoderA decoderB j =
44- lmap (" Couldn't decode Either: " <> _ ) $
45+ lmap (Named " Either" ) $
4546 decodeJObject j >>= \obj -> do
46- tag <- maybe (Left " Expected field ' tag' " ) Right $ FO .lookup " tag" obj
47- val <- maybe (Left " Expected field ' value' " ) Right $ FO .lookup " value" obj
47+ tag <- maybe (Left $ AtKey " tag" MissingValue ) Right $ FO .lookup " tag" obj
48+ val <- maybe (Left $ AtKey " value" MissingValue ) Right $ FO .lookup " value" obj
4849 case toString tag of
4950 Just " Right" -> Right <$> decoderB val
5051 Just " Left" -> Left <$> decoderA val
51- _ -> Left " 'tag' field was not \" Left \" or \" Right \" "
52+ _ -> Left $ AtKey " tag " ( UnexpectedValue tag)
5253
53- decodeNull :: Json -> Either String Unit
54- decodeNull = caseJsonNull (Left " Value is not a null" ) (const $ Right unit)
54+ decodeNull :: Json -> Either JsonDecodeError Unit
55+ decodeNull = caseJsonNull (Left $ TypeMismatch " null" ) (const $ Right unit)
5556
56- decodeBoolean :: Json -> Either String Boolean
57- decodeBoolean = caseJsonBoolean (Left " Value is not a Boolean" ) Right
57+ decodeBoolean :: Json -> Either JsonDecodeError Boolean
58+ decodeBoolean = caseJsonBoolean (Left $ TypeMismatch " Boolean" ) Right
5859
59- decodeNumber :: Json -> Either String Number
60- decodeNumber = caseJsonNumber (Left " Value is not a Number" ) Right
60+ decodeNumber :: Json -> Either JsonDecodeError Number
61+ decodeNumber = caseJsonNumber (Left $ TypeMismatch " Number" ) Right
6162
62- decodeInt :: Json -> Either String Int
63+ decodeInt :: Json -> Either JsonDecodeError Int
6364decodeInt =
64- maybe (Left " Value is not an Integer" ) Right
65+ maybe (Left $ TypeMismatch " Integer" ) Right
6566 <<< fromNumber
6667 <=< decodeNumber
6768
68- decodeString :: Json -> Either String String
69- decodeString = caseJsonString (Left " Value is not a String" ) Right
69+ decodeString :: Json -> Either JsonDecodeError String
70+ decodeString = caseJsonString (Left $ TypeMismatch " String" ) Right
7071
71- decodeNonEmpty_Array :: ∀ a . (Json -> Either String a ) -> Json -> Either String (NonEmpty Array a )
72+ decodeNonEmpty_Array :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (NonEmpty Array a )
7273decodeNonEmpty_Array decoder =
73- lmap (" Couldn't decode NonEmpty Array: " <> _ )
74- <<< (traverse decoder <=< (lmap ( " JSON Array " <> _) <<< rmap (\x -> x.head :| x.tail) <<< note " is empty " <<< Arr .uncons) <=< decodeJArray)
74+ lmap (Named " NonEmpty Array" )
75+ <<< (traverse decoder <=< (rmap (\x -> x.head :| x.tail) <<< note ( TypeMismatch " NonEmpty Array " ) <<< Arr .uncons) <=< decodeJArray)
7576
76- decodeNonEmptyArray :: ∀ a . (Json -> Either String a ) -> Json -> Either String (NonEmptyArray a )
77+ decodeNonEmptyArray :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (NonEmptyArray a )
7778decodeNonEmptyArray decoder =
78- lmap (" Couldn't decode NonEmptyArray: " <> _ )
79- <<< (traverse decoder <=< (lmap ( " JSON Array " <> _) <<< rmap (\x -> NEA .cons' x.head x.tail) <<< note " is empty " <<< Arr .uncons) <=< decodeJArray)
79+ lmap (Named " NonEmptyArray" )
80+ <<< (traverse decoder <=< (rmap (\x -> NEA .cons' x.head x.tail) <<< note ( TypeMismatch " NonEmptyArray " ) <<< Arr .uncons) <=< decodeJArray)
8081
81- decodeNonEmpty_List :: ∀ a . (Json -> Either String a ) -> Json -> Either String (NonEmpty List a )
82+ decodeNonEmpty_List :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (NonEmpty List a )
8283decodeNonEmpty_List decoder =
83- lmap (" Couldn't decode NonEmpty List: " <> _ )
84- <<< (traverse decoder <=< (lmap ( " JSON Array " <> _) <<< rmap (\x -> x.head :| x.tail) <<< note " is empty " <<< L .uncons) <=< map (map fromFoldable) decodeJArray)
84+ lmap (Named " NonEmpty List" )
85+ <<< (traverse decoder <=< (rmap (\x -> x.head :| x.tail) <<< note ( TypeMismatch " NonEmpty List " ) <<< L .uncons) <=< map (map fromFoldable) decodeJArray)
8586
86- decodeNonEmptyList :: ∀ a . (Json -> Either String a ) -> Json -> Either String (NonEmptyList a )
87+ decodeNonEmptyList :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (NonEmptyList a )
8788decodeNonEmptyList decoder =
88- lmap (" Couldn't decode NonEmptyList: " <> _ )
89- <<< (traverse decoder <=< (lmap ( " JSON Array " <> _) <<< rmap (\x -> NEL .cons' x.head x.tail) <<< note " is empty " <<< L .uncons) <=< map (map fromFoldable) decodeJArray)
89+ lmap (Named " NonEmptyList" )
90+ <<< (traverse decoder <=< (rmap (\x -> NEL .cons' x.head x.tail) <<< note ( TypeMismatch " NonEmptyList " ) <<< L .uncons) <=< map (map fromFoldable) decodeJArray)
9091
91- decodeCodePoint :: Json -> Either String CodePoint
92+ decodeCodePoint :: Json -> Either JsonDecodeError CodePoint
9293decodeCodePoint j =
93- maybe (Left $ " Expected character but found: " <> stringify j) Right
94+ maybe (Left $ Named " CodePoint " $ UnexpectedValue j) Right
9495 =<< codePointAt 0 <$> decodeString j
9596
96- decodeForeignObject :: ∀ a . (Json -> Either String a ) -> Json -> Either String (FO.Object a )
97+ decodeForeignObject :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (FO.Object a )
9798decodeForeignObject decoder =
98- lmap (" Couldn't decode ForeignObject: " <> _ )
99+ lmap (Named " ForeignObject" )
99100 <<< (traverse decoder <=< decodeJObject)
100101
101- decodeArray :: ∀ a . (Json -> Either String a ) -> Json -> Either String (Array a )
102+ decodeArray :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (Array a )
102103decodeArray decoder =
103- lmap (" Couldn't decode Array ( " <> _ )
104+ lmap (Named " Array" )
104105 <<< (traverseWithIndex f <=< decodeJArray)
105106 where
106- msg i m = " Failed at index " <> show i <> " ): " <> m
107+ msg i m = AtIndex i m
107108 f i = lmap (msg i) <<< decoder
108109
109- decodeList :: ∀ a . (Json -> Either String a ) -> Json -> Either String (List a )
110+ decodeList :: ∀ a . (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (List a )
110111decodeList decoder =
111- lmap (" Couldn't decode List: " <> _ )
112+ lmap (Named " List" )
112113 <<< (traverse decoder <=< map (map fromFoldable) decodeJArray)
113114
114- decodeSet :: ∀ a . Ord a => (Json -> Either String a ) -> Json -> Either String (S.Set a )
115+ decodeSet :: ∀ a . Ord a => (Json -> Either JsonDecodeError a ) -> Json -> Either JsonDecodeError (S.Set a )
115116decodeSet decoder = map (S .fromFoldable :: List a -> S.Set a ) <<< decodeList decoder
116117
117- decodeMap :: ∀ a b . Ord a => (Json -> Either String a ) -> (Json -> Either String b ) -> Json -> Either String (M.Map a b )
118+ decodeMap :: ∀ a b . Ord a => (Json -> Either JsonDecodeError a ) -> (Json -> Either JsonDecodeError b ) -> Json -> Either JsonDecodeError (M.Map a b )
118119decodeMap decoderA decoderB = map (M .fromFoldable :: List (Tuple a b ) -> M.Map a b ) <<< decodeList (decodeTuple decoderA decoderB)
119120
120- decodeVoid :: Json -> Either String Void
121- decodeVoid _ = Left " Value cannot be Void"
121+ decodeVoid :: Json -> Either JsonDecodeError Void
122+ decodeVoid _ = Left $ UnexpectedValue $ fromString " Value cannot be Void"
122123
123- decodeJArray :: Json -> Either String (Array Json )
124- decodeJArray = maybe (Left " Value is not an Array" ) Right <<< toArray
124+ decodeJArray :: Json -> Either JsonDecodeError (Array Json )
125+ decodeJArray = maybe (Left $ TypeMismatch " Array" ) Right <<< toArray
125126
126- decodeJObject :: Json -> Either String (FO.Object Json )
127- decodeJObject = maybe (Left " Value is not an Object" ) Right <<< toObject
127+ decodeJObject :: Json -> Either JsonDecodeError (FO.Object Json )
128+ decodeJObject = maybe (Left $ TypeMismatch " Object" ) Right <<< toObject
128129
129- getField :: forall a . (Json -> Either String a ) -> FO.Object Json -> String -> Either String a
130+ getField :: forall a . (Json -> Either JsonDecodeError a ) -> FO.Object Json -> String -> Either JsonDecodeError a
130131getField decoder o s =
131132 maybe
132- (Left $ " Expected field " <> show s )
133- (elaborateFailure s <<< decoder)
133+ (Left $ AtKey s MissingValue )
134+ (lmap ( AtKey s) <<< decoder)
134135 (FO .lookup s o)
135136
136- getFieldOptional :: forall a . (Json -> Either String a ) -> FO.Object Json -> String -> Either String (Maybe a )
137+ getFieldOptional :: forall a . (Json -> Either JsonDecodeError a ) -> FO.Object Json -> String -> Either JsonDecodeError (Maybe a )
137138getFieldOptional decoder o s =
138139 maybe
139140 (pure Nothing )
140141 decode
141142 (FO .lookup s o)
142143 where
143- decode json = Just <$> (elaborateFailure s <<< decoder) json
144+ decode json = Just <$> (lmap ( AtKey s) <<< decoder) json
144145
145- getFieldOptional' :: forall a . (Json -> Either String a ) -> FO.Object Json -> String -> Either String (Maybe a )
146+ getFieldOptional' :: forall a . (Json -> Either JsonDecodeError a ) -> FO.Object Json -> String -> Either JsonDecodeError (Maybe a )
146147getFieldOptional' decoder o s =
147148 maybe
148149 (pure Nothing )
@@ -152,10 +153,4 @@ getFieldOptional' decoder o s =
152153 decode json =
153154 if isNull json
154155 then pure Nothing
155- else Just <$> (elaborateFailure s <<< decoder) json
156-
157- elaborateFailure :: ∀ a . String -> Either String a -> Either String a
158- elaborateFailure s e =
159- lmap msg e
160- where
161- msg m = " Failed to decode key '" <> s <> " ': " <> m
156+ else Just <$> (lmap (AtKey s) <<< decoder) json
0 commit comments