1
1
{-# LANGUAGE BangPatterns #-}
2
2
{-# LANGUAGE TypeApplications #-}
3
+ {-# LANGUAGE RankNTypes #-}
3
4
4
5
module Hedgehog.Extras.Test.File
5
6
( createDirectoryIfMissing
@@ -193,60 +194,61 @@ textReadFile filePath = GHC.withFrozenCallStack $ do
193
194
void . H. annotate $ " Reading file: " <> filePath
194
195
H. evalIO $ T. readFile filePath
195
196
196
- -- | Read the 'filePath' file as JSON.
197
- readJsonFile :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> m (Either String Value )
197
+ -- | Read the 'filePath' file as JSON. Use @readJsonFile \@'Value'@ to decode into 'Value'.
198
+ readJsonFile :: forall a m . (MonadTest m , MonadIO m , Y. FromJSON a , HasCallStack ) => FilePath -> m (Either String a )
198
199
readJsonFile filePath = GHC. withFrozenCallStack $ do
199
200
void . H. annotate $ " Reading JSON file: " <> filePath
200
- H. evalIO $ J. eitherDecode @ Value <$> LBS. readFile filePath
201
+ H. evalIO $ J. eitherDecode <$> LBS. readFile filePath
201
202
202
- -- | Read the 'filePath' file as JSON. Same as 'readJsonFile' but fails on error.
203
- readJsonFileOk :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> m Value
203
+ -- | Read the 'filePath' file as JSON. Same as 'readJsonFile' but fails on error. Use
204
+ -- @readJsonFileOk \@'Value'@ to decode into 'Value'.
205
+ readJsonFileOk :: forall a m . (MonadTest m , MonadIO m , Y. FromJSON a , HasCallStack ) => FilePath -> m a
204
206
readJsonFileOk filePath = GHC. withFrozenCallStack $
205
207
H. leftFailM $ readJsonFile filePath
206
208
207
- rewriteLbsJson :: (MonadTest m , HasCallStack ) => (Value -> Value ) -> LBS. ByteString -> m LBS. ByteString
209
+ rewriteLbsJson :: forall a m . (MonadTest m , Y. FromJSON a , Y. ToJSON a , HasCallStack ) => (a -> a ) -> LBS. ByteString -> m LBS. ByteString
208
210
rewriteLbsJson f lbs = GHC. withFrozenCallStack $ do
209
211
case J. eitherDecode lbs of
210
212
Right iv -> return (J. encode (f iv))
211
213
Left msg -> H. failMessage GHC. callStack msg
212
214
213
215
-- | Rewrite the 'filePath' JSON file using the function 'f'.
214
- rewriteJsonFile :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> (Value -> Value ) -> m ()
216
+ rewriteJsonFile :: forall a m . (MonadTest m , MonadIO m , Y. FromJSON a , Y. ToJSON a , HasCallStack ) => FilePath -> (a -> a ) -> m ()
215
217
rewriteJsonFile filePath f = GHC. withFrozenCallStack $ do
216
218
void . H. annotate $ " Rewriting JSON file: " <> filePath
217
219
lbsReadFile filePath >>= rewriteLbsJson f >>= lbsWriteFile filePath
218
220
219
221
-- | Rewrite the 'filePath' JSON file using the function 'f'.
220
- copyRewriteJsonFile :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> FilePath -> (Value -> Value ) -> m ()
222
+ copyRewriteJsonFile :: forall a m . (MonadTest m , MonadIO m , Y. FromJSON a , Y. ToJSON a , HasCallStack ) => FilePath -> FilePath -> (a -> a ) -> m ()
221
223
copyRewriteJsonFile src dst f = GHC. withFrozenCallStack $ do
222
224
void . H. annotate $ " Rewriting JSON from file: " <> src <> " to file " <> dst
223
225
lbsReadFile src >>= rewriteLbsJson f >>= lbsWriteFile dst
224
226
225
227
-- | Read the 'filePath' file as YAML.
226
- readYamlFile :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> m (Either Y. ParseException Value )
228
+ readYamlFile :: forall a m . (MonadTest m , MonadIO m , Y. FromJSON a , HasCallStack ) => FilePath -> m (Either Y. ParseException a )
227
229
readYamlFile filePath = GHC. withFrozenCallStack $ do
228
230
void . H. annotate $ " Reading YAML file: " <> filePath
229
- H. evalIO $ Y. decodeEither' @ Value . LBS. toStrict <$> LBS. readFile filePath
231
+ H. evalIO $ Y. decodeEither' . LBS. toStrict <$> LBS. readFile filePath
230
232
231
233
-- | Read the 'filePath' file as YAML. Same as 'readYamlFile' but fails on error.
232
- readYamlFileOk :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> m Value
234
+ readYamlFileOk :: forall a m . (MonadTest m , MonadIO m , Y. FromJSON a , HasCallStack ) => FilePath -> m a
233
235
readYamlFileOk filePath = GHC. withFrozenCallStack $
234
236
H. leftFailM $ readYamlFile filePath
235
237
236
- rewriteLbsYaml :: (MonadTest m , HasCallStack ) => (Value -> Value ) -> LBS. ByteString -> m LBS. ByteString
238
+ rewriteLbsYaml :: forall a m . (MonadTest m , Y. FromJSON a , Y. ToJSON a , HasCallStack ) => (a -> a ) -> LBS. ByteString -> m LBS. ByteString
237
239
rewriteLbsYaml f lbs = GHC. withFrozenCallStack $ do
238
240
case Y. decodeEither' (LBS. toStrict lbs) of
239
241
Right iv -> return (J. encode (f iv))
240
242
Left msg -> H. failMessage GHC. callStack (show msg)
241
243
242
244
-- | Rewrite the 'filePath' YAML file using the function 'f'.
243
- rewriteYamlFile :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> (Value -> Value ) -> m ()
245
+ rewriteYamlFile :: forall a m . (MonadTest m , MonadIO m , Y. FromJSON a , Y. ToJSON a , HasCallStack ) => FilePath -> (a -> a ) -> m ()
244
246
rewriteYamlFile filePath f = GHC. withFrozenCallStack $ do
245
247
void . H. annotate $ " Rewriting YAML file: " <> filePath
246
248
lbsReadFile filePath >>= rewriteLbsYaml f >>= lbsWriteFile filePath
247
249
248
250
-- | Rewrite the 'filePath' YAML file using the function 'f'.
249
- copyRewriteYamlFile :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> FilePath -> (Value -> Value ) -> m ()
251
+ copyRewriteYamlFile :: forall a m . (MonadTest m , MonadIO m , Y. FromJSON a , Y. ToJSON a , HasCallStack ) => FilePath -> FilePath -> (a -> a ) -> m ()
250
252
copyRewriteYamlFile src dst f = GHC. withFrozenCallStack $ do
251
253
void . H. annotate $ " Rewriting YAML from file: " <> src <> " to file " <> dst
252
254
lbsReadFile src >>= rewriteLbsYaml f >>= lbsWriteFile dst
@@ -264,15 +266,15 @@ cat filePath = GHC.withFrozenCallStack $ do
264
266
-- | Assert the 'filePath' can be parsed as JSON.
265
267
assertIsJsonFile :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> m ()
266
268
assertIsJsonFile fp = GHC. withFrozenCallStack $ do
267
- jsonResult <- readJsonFile fp
269
+ jsonResult <- readJsonFile @ Value fp
268
270
case jsonResult of
269
271
Right _ -> return ()
270
272
Left msg -> H. failMessage GHC. callStack msg
271
273
272
274
-- | Assert the 'filePath' can be parsed as YAML.
273
275
assertIsYamlFile :: (MonadTest m , MonadIO m , HasCallStack ) => FilePath -> m ()
274
276
assertIsYamlFile fp = GHC. withFrozenCallStack $ do
275
- result <- readJsonFile fp
277
+ result <- readJsonFile @ Value fp
276
278
case result of
277
279
Right _ -> return ()
278
280
Left msg -> H. failMessage GHC. callStack msg
0 commit comments