@@ -38,11 +38,16 @@ module Data.Aeson
38
38
, eitherDecode
39
39
, eitherDecode'
40
40
, encode
41
+ , encodeFile
41
42
-- ** Variants for strict bytestrings
42
43
, decodeStrict
44
+ , decodeFileStrict
43
45
, decodeStrict'
46
+ , decodeFileStrict'
44
47
, eitherDecodeStrict
48
+ , eitherDecodeFileStrict
45
49
, eitherDecodeStrict'
50
+ , eitherDecodeFileStrict'
46
51
-- * Core JSON types
47
52
, Value (.. )
48
53
, Encoding
@@ -143,6 +148,10 @@ import qualified Data.ByteString.Lazy as L
143
148
encode :: (ToJSON a ) => a -> L. ByteString
144
149
encode = encodingToLazyByteString . toEncoding
145
150
151
+ -- | Efficiently serialize a JSON value as a lazy 'L.ByteString' and write it to a file.
152
+ encodeFile :: (ToJSON a ) => FilePath -> a -> IO ()
153
+ encodeFile fp = L. writeFile fp . encode
154
+
146
155
-- | Efficiently deserialize a JSON value from a lazy 'L.ByteString'.
147
156
-- If this fails due to incomplete or invalid input, 'Nothing' is
148
157
-- returned.
@@ -169,6 +178,18 @@ decodeStrict :: (FromJSON a) => B.ByteString -> Maybe a
169
178
decodeStrict = decodeStrictWith jsonEOF fromJSON
170
179
{-# INLINE decodeStrict #-}
171
180
181
+ -- | Efficiently deserialize a JSON value from a file.
182
+ -- If this fails due to incomplete or invalid input, 'Nothing' is
183
+ -- returned.
184
+ --
185
+ -- The input file's content must consist solely of a JSON document,
186
+ -- with no trailing data except for whitespace.
187
+ --
188
+ -- This function parses immediately, but defers conversion. See
189
+ -- 'json' for details.
190
+ decodeFileStrict :: (FromJSON a ) => FilePath -> IO (Maybe a )
191
+ decodeFileStrict = fmap decodeStrict . B. readFile
192
+
172
193
-- | Efficiently deserialize a JSON value from a lazy 'L.ByteString'.
173
194
-- If this fails due to incomplete or invalid input, 'Nothing' is
174
195
-- returned.
@@ -195,6 +216,18 @@ decodeStrict' :: (FromJSON a) => B.ByteString -> Maybe a
195
216
decodeStrict' = decodeStrictWith jsonEOF' fromJSON
196
217
{-# INLINE decodeStrict' #-}
197
218
219
+ -- | Efficiently deserialize a JSON value from a file.
220
+ -- If this fails due to incomplete or invalid input, 'Nothing' is
221
+ -- returned.
222
+ --
223
+ -- The input file's content must consist solely of a JSON document,
224
+ -- with no trailing data except for whitespace.
225
+ --
226
+ -- This function parses and performs conversion immediately. See
227
+ -- 'json'' for details.
228
+ decodeFileStrict' :: (FromJSON a ) => FilePath -> IO (Maybe a )
229
+ decodeFileStrict' = fmap decodeStrict' . B. readFile
230
+
198
231
eitherFormatError :: Either (JSONPath , String ) a -> Either String a
199
232
eitherFormatError = either (Left . uncurry formatError) Right
200
233
{-# INLINE eitherFormatError #-}
@@ -210,6 +243,12 @@ eitherDecodeStrict =
210
243
eitherFormatError . eitherDecodeStrictWith jsonEOF ifromJSON
211
244
{-# INLINE eitherDecodeStrict #-}
212
245
246
+ -- | Like 'decodeFileStrict' but returns an error message when decoding fails.
247
+ eitherDecodeFileStrict :: (FromJSON a ) => FilePath -> IO (Either String a )
248
+ eitherDecodeFileStrict =
249
+ fmap (eitherFormatError . eitherDecodeStrictWith jsonEOF ifromJSON) . B. readFile
250
+ {-# INLINE eitherDecodeFileStrict #-}
251
+
213
252
-- | Like 'decode'' but returns an error message when decoding fails.
214
253
eitherDecode' :: (FromJSON a ) => L. ByteString -> Either String a
215
254
eitherDecode' = eitherFormatError . eitherDecodeWith jsonEOF' ifromJSON
@@ -221,6 +260,12 @@ eitherDecodeStrict' =
221
260
eitherFormatError . eitherDecodeStrictWith jsonEOF' ifromJSON
222
261
{-# INLINE eitherDecodeStrict' #-}
223
262
263
+ -- | Like 'decodeFileStrict'' but returns an error message when decoding fails.
264
+ eitherDecodeFileStrict' :: (FromJSON a ) => FilePath -> IO (Either String a )
265
+ eitherDecodeFileStrict' =
266
+ fmap (eitherFormatError . eitherDecodeStrictWith jsonEOF' ifromJSON) . B. readFile
267
+ {-# INLINE eitherDecodeFileStrict' #-}
268
+
224
269
-- $use
225
270
--
226
271
-- This section contains basic information on the different ways to
0 commit comments