{-# OPTIONS_HADDOCK hide #-} module Polysemy.Test.Hedgehog where import qualified Hedgehog as Native import Hedgehog (TestT, (===)) import qualified Polysemy.Test.Data.Hedgehog as Hedgehog import Polysemy.Test.Data.Hedgehog (Hedgehog) -- |Interpret 'Hedgehog' into @'TestT' IO@ by simple embedding of the native combinators. interpretHedgehog :: Member (Embed (TestT IO)) r => InterpreterFor Hedgehog r interpretHedgehog = interpret \case Hedgehog.LiftH t -> embed t Hedgehog.Assert v -> embed (Native.assert v) Hedgehog.AssertEqual a1 a2 -> embed (a1 === a2) Hedgehog.EvalEither e -> embed (Native.evalEither e) Hedgehog.AssertRight a e -> embed ((a ===) =<< Native.evalEither e)