Skip to content

Commit

Permalink
Add a MonadBaseControl instance for PropertyT
Browse files Browse the repository at this point in the history
Under an assumption I believe is reasonable (see
[this issue](basvandijk/monad-control#48) and
[this SO question](https://stackoverflow.com/questions/58105759/monadbasecontrol-laws)
I believe it is possible to write a lawful `MonadBaseControl` instance
for `CofreeT`, and therefore also for the `TreeT`, `GenT`, and
`PropertyT` types in this package. I can't say for sure whether it
"makes sense", but hey, maybe it does.
  • Loading branch information
treeowl committed Sep 25, 2019
1 parent 8b02b09 commit a439b09
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 0 deletions.
25 changes: 25 additions & 0 deletions hedgehog/src/Hedgehog/Internal/Gen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,9 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-} -- MonadBase
#if __GLASGOW_HASKELL__ >= 806
{-# LANGUAGE DerivingVia #-}
#endif
module Hedgehog.Internal.Gen (
-- * Transformer
Gen
Expand Down Expand Up @@ -165,6 +168,7 @@ module Hedgehog.Internal.Gen (
import Control.Applicative (Alternative(..),liftA2)
import Control.Monad (MonadPlus(..), filterM, replicateM, join)
import Control.Monad.Base (MonadBase(..))
import Control.Monad.Trans.Control (MonadBaseControl(..))
import Control.Monad.Catch (MonadThrow(..), MonadCatch(..))
import Control.Monad.Error.Class (MonadError(..))
import Control.Monad.Fail (MonadFail (..))
Expand All @@ -190,6 +194,9 @@ import Data.Bifunctor (first)
import Data.ByteString (ByteString)
import qualified Data.ByteString as ByteString
import qualified Data.Char as Char
#if __GLASGOW_HASKELL__ < 806
import Data.Coerce (coerce)
#endif
import Data.Foldable (for_, toList)
import Data.Functor.Identity (Identity(..))
import Data.Int (Int8, Int16, Int32, Int64)
Expand Down Expand Up @@ -587,6 +594,24 @@ instance MonadBase b m => MonadBase b (GenT m) where
liftBase =
lift . liftBase

#if __GLASGOW_HASKELL__ >= 806
deriving via (ReaderT Size (ReaderT Seed (TreeT (MaybeT m))))
instance MonadBaseControl b m => MonadBaseControl b (GenT m)
#else
instance MonadBaseControl b m => MonadBaseControl b (GenT m) where
type StM (GenT m) a = StM (GloopT m) a
liftBaseWith g = gloopToGen $ liftBaseWith $ \q -> g (\gen -> q (genToGloop gen))
restoreM = gloopToGen . restoreM

type GloopT m = ReaderT Size (ReaderT Seed (TreeT (MaybeT m)))

gloopToGen :: GloopT m a -> GenT m a
gloopToGen = coerce

genToGloop :: GenT m a -> GloopT m a
genToGloop = coerce
#endif

instance MonadThrow m => MonadThrow (GenT m) where
throwM =
lift . throwM
Expand Down
1 change: 1 addition & 0 deletions hedgehog/src/Hedgehog/Internal/Property.hs
Original file line number Diff line number Diff line change
Expand Up @@ -186,6 +186,7 @@ newtype PropertyT m a =
)
-- NOTE: Move this to the deriving list above when we drop 7.10
deriving instance MonadResource m => MonadResource (PropertyT m)
deriving instance MonadBaseControl b m => MonadBaseControl b (PropertyT m)

-- | A test monad allows the assertion of expectations.
--
Expand Down
6 changes: 6 additions & 0 deletions hedgehog/src/Hedgehog/Internal/Tree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -66,6 +66,7 @@ import Data.Functor.Classes (showsUnaryWith, showsBinaryWith)
import qualified Data.Maybe as Maybe

import Hedgehog.Internal.Distributive
import Control.Monad.Trans.Control (MonadBaseControl (..))

import Prelude hiding (filter)

Expand All @@ -91,6 +92,11 @@ newtype TreeT m a =
runTreeT :: m (NodeT m a)
}

instance MonadBaseControl b m => MonadBaseControl b (TreeT m) where
type StM (TreeT m) a = StM m (NodeT m a)
liftBaseWith f = TreeT $ liftBaseWith (\g -> pure <$> f (g . runTreeT))
restoreM = TreeT . restoreM

-- | A node in a rose tree.
--
type Node =
Expand Down

0 comments on commit a439b09

Please sign in to comment.