Skip to content

Commit 25fecf8

Browse files
committed
Allow reading files into any FromJSON
1 parent 8a40189 commit 25fecf8

File tree

1 file changed

+18
-16
lines changed

1 file changed

+18
-16
lines changed

src/Hedgehog/Extras/Test/File.hs

+18-16
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE BangPatterns #-}
22
{-# LANGUAGE TypeApplications #-}
3+
{-# LANGUAGE RankNTypes #-}
34

45
module Hedgehog.Extras.Test.File
56
( createDirectoryIfMissing
@@ -193,60 +194,61 @@ textReadFile filePath = GHC.withFrozenCallStack $ do
193194
void . H.annotate $ "Reading file: " <> filePath
194195
H.evalIO $ T.readFile filePath
195196

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)
198199
readJsonFile filePath = GHC.withFrozenCallStack $ do
199200
void . H.annotate $ "Reading JSON file: " <> filePath
200-
H.evalIO $ J.eitherDecode @Value <$> LBS.readFile filePath
201+
H.evalIO $ J.eitherDecode <$> LBS.readFile filePath
201202

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
204206
readJsonFileOk filePath = GHC.withFrozenCallStack $
205207
H.leftFailM $ readJsonFile filePath
206208

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
208210
rewriteLbsJson f lbs = GHC.withFrozenCallStack $ do
209211
case J.eitherDecode lbs of
210212
Right iv -> return (J.encode (f iv))
211213
Left msg -> H.failMessage GHC.callStack msg
212214

213215
-- | 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 ()
215217
rewriteJsonFile filePath f = GHC.withFrozenCallStack $ do
216218
void . H.annotate $ "Rewriting JSON file: " <> filePath
217219
lbsReadFile filePath >>= rewriteLbsJson f >>= lbsWriteFile filePath
218220

219221
-- | 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 ()
221223
copyRewriteJsonFile src dst f = GHC.withFrozenCallStack $ do
222224
void . H.annotate $ "Rewriting JSON from file: " <> src <> " to file " <> dst
223225
lbsReadFile src >>= rewriteLbsJson f >>= lbsWriteFile dst
224226

225227
-- | 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)
227229
readYamlFile filePath = GHC.withFrozenCallStack $ do
228230
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
230232

231233
-- | 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
233235
readYamlFileOk filePath = GHC.withFrozenCallStack $
234236
H.leftFailM $ readYamlFile filePath
235237

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
237239
rewriteLbsYaml f lbs = GHC.withFrozenCallStack $ do
238240
case Y.decodeEither' (LBS.toStrict lbs) of
239241
Right iv -> return (J.encode (f iv))
240242
Left msg -> H.failMessage GHC.callStack (show msg)
241243

242244
-- | 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 ()
244246
rewriteYamlFile filePath f = GHC.withFrozenCallStack $ do
245247
void . H.annotate $ "Rewriting YAML file: " <> filePath
246248
lbsReadFile filePath >>= rewriteLbsYaml f >>= lbsWriteFile filePath
247249

248250
-- | 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 ()
250252
copyRewriteYamlFile src dst f = GHC.withFrozenCallStack $ do
251253
void . H.annotate $ "Rewriting YAML from file: " <> src <> " to file " <> dst
252254
lbsReadFile src >>= rewriteLbsYaml f >>= lbsWriteFile dst
@@ -264,15 +266,15 @@ cat filePath = GHC.withFrozenCallStack $ do
264266
-- | Assert the 'filePath' can be parsed as JSON.
265267
assertIsJsonFile :: (MonadTest m, MonadIO m, HasCallStack) => FilePath -> m ()
266268
assertIsJsonFile fp = GHC.withFrozenCallStack $ do
267-
jsonResult <- readJsonFile fp
269+
jsonResult <- readJsonFile @Value fp
268270
case jsonResult of
269271
Right _ -> return ()
270272
Left msg -> H.failMessage GHC.callStack msg
271273

272274
-- | Assert the 'filePath' can be parsed as YAML.
273275
assertIsYamlFile :: (MonadTest m, MonadIO m, HasCallStack) => FilePath -> m ()
274276
assertIsYamlFile fp = GHC.withFrozenCallStack $ do
275-
result <- readJsonFile fp
277+
result <- readJsonFile @Value fp
276278
case result of
277279
Right _ -> return ()
278280
Left msg -> H.failMessage GHC.callStack msg

0 commit comments

Comments
 (0)