Skip to content

Commit

Permalink
Merge pull request #255 from endgame/resourcet-hoist
Browse files Browse the repository at this point in the history
hedgehog-example: relax resourcet to < 1.3
  • Loading branch information
jacobstanley authored Mar 20, 2019
2 parents fc98d47 + 060369f commit 961479e
Show file tree
Hide file tree
Showing 2 changed files with 6 additions and 5 deletions.
2 changes: 1 addition & 1 deletion hedgehog-example/hedgehog-example.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ library
, pretty-show >= 1.6 && < 1.10
, process >= 1.2 && < 1.7
, QuickCheck >= 2.7 && < 2.13
, resourcet >= 1.1 && < 1.2
, resourcet >= 1.1 && < 1.3
, temporary-resourcet >= 0.1 && < 0.2
, text >= 1.1 && < 1.3
, transformers >= 0.4 && < 0.6
Expand Down
9 changes: 5 additions & 4 deletions hedgehog-example/src/Test/Example/Resource.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

module Test.Example.Resource where

import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Morph (hoist)
import Control.Monad.Trans.Except (ExceptT, throwE)
import Control.Monad.Trans.Resource (runResourceT)

Expand All @@ -15,8 +16,8 @@ import System.FilePath ((</>))
import qualified System.IO.Temp as Temp
import System.Process

data ProcessFailed =
ProcessFailed !Int
newtype ProcessFailed =
ProcessFailed Int
deriving (Show)

unixSort :: MonadIO m => FilePath -> FilePath -> ExceptT ProcessFailed m ()
Expand All @@ -43,7 +44,7 @@ prop_unix_sort =
Gen.list (Range.linear 0 100) $
Gen.string (Range.constant 1 5) Gen.alpha

test . runResourceT $ do
test . hoist runResourceT $ do
(_, dir) <- Temp.createTempDirectory Nothing "prop_dir"

let input = dir </> "input"
Expand Down

0 comments on commit 961479e

Please sign in to comment.