{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fexpose-all-unfoldings #-}
{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE OverloadedStrings #-}
module PredicateTransformers
( Predicatory(..)
, Exceptional(..)
, PredicateFailed(..)
, Pred
, PT
, predJust
, predLeft
, predRight
, endingWith
, startingWith
, soleElementOf
, soleElement
, match
, kth
, predList
, predful
, predCompose
, allTrue
, allOf1
, pattern (:=>)
, pair
, pt
, (?)
, traced
, tracedShow
, traceFailShow
, traceFail
, something
, forced
, equals
, satAll
)
where
import Control.DeepSeq (NFData, force)
import Control.Exception
import Control.Lens hiding (index)
import Control.Monad
import Data.Foldable (toList)
import Data.Functor.Rep (Representable (..))
import Data.Typeable
import Debug.Trace
import System.IO.Unsafe
import Control.Concurrent (myThreadId)
import GHC.Conc (pseq)
import GHC.Stack
import Text.Pretty.Simple
import qualified Prettyprinter as PP
import qualified Prettyprinter.Render.String as PP
import Debug.RecoverRTTI
import qualified Data.Text.Lazy as TL
class Predicatory a where
otherHand :: a -> a -> a
also :: a -> a -> a
stop :: HasCallStack => v -> PP.Doc ann -> a
continue :: a
{-# MINIMAL otherHand, also, stop, continue #-}
instance Predicatory a => Predicatory (e -> a) where
(e -> a
f otherHand :: (e -> a) -> (e -> a) -> e -> a
`otherHand` e -> a
f') e
e = e -> a
f e
e a -> a -> a
forall a. Predicatory a => a -> a -> a
`otherHand` e -> a
f' e
e
(e -> a
f also :: (e -> a) -> (e -> a) -> e -> a
`also` e -> a
f') e
e = e -> a
f e
e a -> a -> a
forall a. Predicatory a => a -> a -> a
`also` e -> a
f' e
e
stop :: forall v ann. HasCallStack => v -> Doc ann -> e -> a
stop v
v Doc ann
expected = (HasCallStack => e -> a) -> e -> a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack ((HasCallStack => e -> a) -> e -> a)
-> (HasCallStack => e -> a) -> e -> a
forall a b. (a -> b) -> a -> b
$ \e
_ -> v -> Doc ann -> a
forall a v ann. (Predicatory a, HasCallStack) => v -> Doc ann -> a
forall v ann. HasCallStack => v -> Doc ann -> a
stop v
v Doc ann
expected
continue :: e -> a
continue = \e
_ -> a
forall a. Predicatory a => a
continue
infixr 3 `also`
infixr 2 `otherHand`
class Exceptional a where
assess :: a -> IO () -> a
instance Exceptional a => Exceptional (e -> a) where
assess :: (e -> a) -> IO () -> e -> a
assess e -> a
f IO ()
act = \e
e -> a -> IO () -> a
forall a. Exceptional a => a -> IO () -> a
assess (e -> a
f e
e) IO ()
act
data PredicateFailed = forall actual ann. PredicateFailed !CallStack (PP.Doc ann) actual
deriving (Typeable)
instance Show PredicateFailed where
show :: PredicateFailed -> String
show = PredicateFailed -> String
forall e. Exception e => e -> String
displayException
anythingToStringPretty :: a -> String
anythingToStringPretty :: forall a. a -> String
anythingToStringPretty = Text -> String
TL.unpack (Text -> String) -> (a -> Text) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OutputOptions -> String -> Text
pStringOpt OutputOptions
opts (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. a -> String
anythingToString
where
opts :: OutputOptions
opts = OutputOptions
defaultOutputOptionsNoColor
{ outputOptionsIndentAmount = 2
, outputOptionsPageWidth = 120
, outputOptionsCompact = True
, outputOptionsCompactParens = True
, outputOptionsInitialIndent = 0
}
instance Exception PredicateFailed where
displayException :: PredicateFailed -> String
displayException (PredicateFailed CallStack
cs Doc ann
expected actual
actual)
= SimpleDocStream ann -> String
forall ann. SimpleDocStream ann -> String
PP.renderString (SimpleDocStream ann -> String) -> SimpleDocStream ann -> String
forall a b. (a -> b) -> a -> b
$ LayoutOptions -> Doc ann -> SimpleDocStream ann
forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
PP.layoutSmart LayoutOptions
PP.defaultLayoutOptions (Doc ann -> SimpleDocStream ann) -> Doc ann -> SimpleDocStream ann
forall a b. (a -> b) -> a -> b
$
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
PP.sep
[ Doc ann
"Actual" Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann
forall ann. Doc ann
PP.softline Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
PP.pretty String
prettyActual
, Doc ann
"but expected" Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann
forall ann. Doc ann
PP.softline Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann
expected
] Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann
forall ann. Doc ann
PP.hardline Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
PP.pretty (CallStack -> String
prettyCallStack CallStack
cs)
where
prettyActual :: String
prettyActual = actual -> String
forall a. a -> String
anythingToStringPretty actual
actual
instance Predicatory Bool where
otherHand :: Bool -> Bool -> Bool
otherHand = Bool -> Bool -> Bool
(||)
also :: Bool -> Bool -> Bool
also = Bool -> Bool -> Bool
(&&)
stop :: forall v ann. HasCallStack => v -> Doc ann -> Bool
stop v
_ Doc ann
_ = Bool
False
continue :: Bool
continue = Bool
True
instance Exceptional Bool where
assess :: Bool -> IO () -> Bool
assess Bool
b IO ()
act
| Bool
b = Bool
b
| Bool
otherwise = IO () -> ()
forall a. IO a -> a
unsafePerformIO IO ()
act () -> Bool -> Bool
forall a b. a -> b -> b
`pseq` Bool
b
instance a ~ () => Predicatory (IO a) where
otherHand :: IO a -> IO a -> IO a
otherHand IO a
x IO a
y = do
IO a -> [Handler a] -> IO a
forall a. IO a -> [Handler a] -> IO a
catches IO a
x
[ (SomeAsyncException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler ((SomeAsyncException -> IO a) -> Handler a)
-> (SomeAsyncException -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \(SomeAsyncException
ex :: SomeAsyncException) -> do
ThreadId
tid <- IO ThreadId
myThreadId
ThreadId -> SomeAsyncException -> IO ()
forall e. Exception e => ThreadId -> e -> IO ()
throwTo ThreadId
tid SomeAsyncException
ex
, (SomeException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler ((SomeException -> IO a) -> Handler a)
-> (SomeException -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \(SomeException
_ex :: SomeException) -> IO a
y
]
also :: IO a -> IO a -> IO a
also = IO a -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
(>>)
stop :: forall v ann. HasCallStack => v -> Doc ann -> IO a
stop v
v Doc ann
expected = PredicateFailed -> IO a
forall e a. Exception e => e -> IO a
throwIO (CallStack -> Doc ann -> v -> PredicateFailed
forall actual ann.
CallStack -> Doc ann -> actual -> PredicateFailed
PredicateFailed (CallStack -> CallStack
popCallStack CallStack
HasCallStack => CallStack
callStack) Doc ann
expected v
v)
continue :: IO a
continue = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
instance a ~ () => Exceptional (IO a) where
assess :: IO a -> IO () -> IO a
assess IO a
x IO ()
act =
IO a -> [Handler a] -> IO a
forall a. IO a -> [Handler a] -> IO a
catches IO a
x
[ (SomeAsyncException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler ((SomeAsyncException -> IO a) -> Handler a)
-> (SomeAsyncException -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \(SomeAsyncException
ex :: SomeAsyncException) -> do
ThreadId
tid <- IO ThreadId
myThreadId
ThreadId -> SomeAsyncException -> IO ()
forall e. Exception e => ThreadId -> e -> IO ()
throwTo ThreadId
tid SomeAsyncException
ex
, (SomeException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler ((SomeException -> IO a) -> Handler a)
-> (SomeException -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \(SomeException
ex :: SomeException) ->
IO ()
act IO () -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> SomeException -> IO a
forall e a. Exception e => e -> IO a
throwIO SomeException
ex
]
type Pred p a = a -> p
type PT p a b = Pred p a -> Pred p b
predJust :: Predicatory p => PT p a (Maybe a)
predJust :: forall p a. Predicatory p => PT p a (Maybe a)
predJust = Prism' (Maybe a) a -> PT p a (Maybe a)
forall p s a. Predicatory p => Prism' s a -> PT p a s
match p a (f a) -> p (Maybe a) (f (Maybe a))
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
Prism' (Maybe a) a
_Just
predLeft :: Predicatory p => PT p e (Either e a)
predLeft :: forall p e a. Predicatory p => PT p e (Either e a)
predLeft = Prism' (Either e a) e -> PT p e (Either e a)
forall p s a. Predicatory p => Prism' s a -> PT p a s
match p e (f e) -> p (Either e a) (f (Either e a))
forall a c b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Either a c) (f (Either b c))
Prism' (Either e a) e
_Left
predRight :: Predicatory p => PT p a (Either e a)
predRight :: forall p a e. Predicatory p => PT p a (Either e a)
predRight = Prism' (Either e a) a -> PT p a (Either e a)
forall p s a. Predicatory p => Prism' s a -> PT p a s
match p a (f a) -> p (Either e a) (f (Either e a))
forall c a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Either c a) (f (Either c b))
Prism' (Either e a) a
_Right
endingWith :: (HasCallStack, Predicatory p, Foldable f) => PT p a (f a)
endingWith :: forall p (f :: * -> *) a.
(HasCallStack, Predicatory p, Foldable f) =>
PT p a (f a)
endingWith Pred p a
_ actual :: f a
actual@(f a -> [a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList -> []) = f a -> Doc Any -> p
forall a v ann. (Predicatory a, HasCallStack) => v -> Doc ann -> a
forall v ann. HasCallStack => v -> Doc ann -> p
stop f a
actual Doc Any
"nonempty foldable"
endingWith Pred p a
p (f a -> [a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList -> [a]
xs) = Pred p a
p Pred p a -> Pred p a
forall a b. (a -> b) -> a -> b
$ [a] -> a
forall a. HasCallStack => [a] -> a
last [a]
xs
startingWith :: (HasCallStack, Predicatory p, Foldable f) => PT p a (f a)
startingWith :: forall p (f :: * -> *) a.
(HasCallStack, Predicatory p, Foldable f) =>
PT p a (f a)
startingWith Pred p a
_ actual :: f a
actual@(f a -> [a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList -> []) = f a -> Doc Any -> p
forall a v ann. (Predicatory a, HasCallStack) => v -> Doc ann -> a
forall v ann. HasCallStack => v -> Doc ann -> p
stop f a
actual Doc Any
"nonempty foldable"
startingWith Pred p a
p (f a -> [a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList -> (a
x : [a]
_)) = Pred p a
p a
x
soleElementOf :: (HasCallStack, Predicatory p) => Fold s a -> PT p a s
soleElementOf :: forall p s a. (HasCallStack, Predicatory p) => Fold s a -> PT p a s
soleElementOf Fold s a
f Pred p a
p (Getting (Endo [a]) s a -> s -> [a]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
Fold s a
f -> [a
x]) = Pred p a
p a
x
soleElementOf Fold s a
_ Pred p a
_ s
actual = s -> Doc Any -> p
forall a v ann. (Predicatory a, HasCallStack) => v -> Doc ann -> a
forall v ann. HasCallStack => v -> Doc ann -> p
stop s
actual Doc Any
"only one element targeted by fold"
soleElement :: (Predicatory p, Foldable f) => PT p a (f a)
soleElement :: forall p (f :: * -> *) a.
(Predicatory p, Foldable f) =>
PT p a (f a)
soleElement = Fold (f a) a -> PT p a (f a)
forall p s a. (HasCallStack, Predicatory p) => Fold s a -> PT p a s
soleElementOf (a -> f a) -> f a -> f (f a)
Fold (f a) a
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
IndexedFold Int (f a) a
folded
match :: Predicatory p => Prism' s a -> PT p a s
match :: forall p s a. Predicatory p => Prism' s a -> PT p a s
match = Fold s a -> PT p a s
Prism' s a -> PT p a s
forall p s a. (HasCallStack, Predicatory p) => Fold s a -> PT p a s
soleElementOf
kth :: (Predicatory p, Foldable f) => Int -> PT p a (f a)
kth :: forall p (f :: * -> *) a.
(Predicatory p, Foldable f) =>
Int -> PT p a (f a)
kth Int
k Pred p a
p = PT p a [a]
forall p (f :: * -> *) a.
(HasCallStack, Predicatory p, Foldable f) =>
PT p a (f a)
startingWith Pred p a
p ([a] -> p) -> (f a -> [a]) -> f a -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
k ([a] -> [a]) -> (f a -> [a]) -> f a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
predList :: (HasCallStack, Predicatory p) => [Pred p a] -> [a] -> p
predList :: forall p a. (HasCallStack, Predicatory p) => [Pred p a] -> [a] -> p
predList [Pred p a]
ps [a]
xs
| Int
psl Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs = (p -> p -> p) -> p -> [p] -> p
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr p -> p -> p
forall a. Predicatory a => a -> a -> a
also p
forall a. Predicatory a => a
continue ((Pred p a -> Pred p a) -> [Pred p a] -> [a] -> [p]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Pred p a -> Pred p a
forall a b. (a -> b) -> a -> b
($) [Pred p a]
ps [a]
xs)
| Bool
otherwise = [a] -> Doc Any -> p
forall a v ann. (Predicatory a, HasCallStack) => v -> Doc ann -> a
forall v ann. HasCallStack => v -> Doc ann -> p
stop [a]
xs (Doc Any -> p) -> Doc Any -> p
forall a b. (a -> b) -> a -> b
$ Doc Any
"list with length " Doc Any -> Doc Any -> Doc Any
forall a. Semigroup a => a -> a -> a
<> Int -> Doc Any
forall ann. Int -> Doc ann
forall a ann. Pretty a => a -> Doc ann
PP.pretty Int
psl
where
psl :: Int
psl = [Pred p a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Pred p a]
ps
predful ::
(HasCallStack, Predicatory p, Eq (f ()), Functor f, Foldable f) =>
f (Pred p a) ->
Pred p (f a)
predful :: forall p (f :: * -> *) a.
(HasCallStack, Predicatory p, Eq (f ()), Functor f, Foldable f) =>
f (Pred p a) -> Pred p (f a)
predful f (Pred p a)
preds f a
values
| f (Pred p a) -> f ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void f (Pred p a)
preds f () -> f () -> Bool
forall a. Eq a => a -> a -> Bool
== f a -> f ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void f a
values =
[Pred p a] -> [a] -> p
forall p a. (HasCallStack, Predicatory p) => [Pred p a] -> [a] -> p
predList (f (Pred p a) -> [Pred p a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (Pred p a)
preds) (f a -> [a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f a
values)
| Bool
otherwise =
f a -> Doc Any -> p
forall a v ann. (Predicatory a, HasCallStack) => v -> Doc ann -> a
forall v ann. HasCallStack => v -> Doc ann -> p
stop f a
values (Doc Any
"shape equal to that of" Doc Any -> Doc Any -> Doc Any
forall a. Semigroup a => a -> a -> a
<> String -> Doc Any
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
PP.pretty (f (Pred p a) -> String
forall a. a -> String
anythingToStringPretty f (Pred p a)
preds))
predCompose ::
Representable f =>
f (Pred p a) ->
f a ->
f p
predCompose :: forall (f :: * -> *) p a.
Representable f =>
f (Pred p a) -> f a -> f p
predCompose f (Pred p a)
pr f a
fa = (Rep f -> p) -> f p
forall a. (Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate (\Rep f
r -> f (Pred p a) -> Rep f -> Pred p a
forall a. f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f (Pred p a)
pr Rep f
r Pred p a -> Pred p a
forall a b. (a -> b) -> a -> b
$ f a -> Rep f -> a
forall a. f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
index f a
fa Rep f
r)
allTrue :: (Predicatory p, Foldable f) => f (Pred p a) -> Pred p a
allTrue :: forall p (f :: * -> *) a.
(Predicatory p, Foldable f) =>
f (Pred p a) -> Pred p a
allTrue f (Pred p a)
ps a
a = (Pred p a -> p -> p) -> p -> f (Pred p a) -> p
forall a b. (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\Pred p a
p p
r -> Pred p a
p a
a p -> p -> p
forall a. Predicatory a => a -> a -> a
`also` p
r) p
forall a. Predicatory a => a
continue f (Pred p a)
ps
allOf1 :: (HasCallStack, Predicatory p) => Fold s a -> PT p a s
allOf1 :: forall p s a. (HasCallStack, Predicatory p) => Fold s a -> PT p a s
allOf1 Fold s a
g Pred p a
p s
vs
| Getting Any s a -> s -> Bool
forall s a. Getting Any s a -> s -> Bool
notNullOf Getting Any s a
Fold s a
g s
vs =
Getting (Endo p) s a -> (a -> p -> p) -> p -> s -> p
forall r s a. Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r
foldrOf Getting (Endo p) s a
Fold s a
g (\a
x p
r -> Pred p a
p a
x p -> p -> p
forall a. Predicatory a => a -> a -> a
`also` p
r) p
forall a. Predicatory a => a
continue s
vs
| Bool
otherwise = s -> Doc Any -> p
forall a v ann. (Predicatory a, HasCallStack) => v -> Doc ann -> a
forall v ann. HasCallStack => v -> Doc ann -> p
stop s
vs Doc Any
"non-empty for fold"
pattern (:=>) :: a -> b -> (a, b)
pattern a $m:=> :: forall {r} {a} {b}. (a, b) -> (a -> b -> r) -> ((# #) -> r) -> r
$b:=> :: forall a b. a -> b -> (a, b)
:=> b = (a, b)
pair :: Predicatory p => Pred p a -> Pred p b -> Pred p (a, b)
pair :: forall p a b.
Predicatory p =>
Pred p a -> Pred p b -> Pred p (a, b)
pair Pred p a
f Pred p b
s (a
a, b
b) = Pred p a
f a
a p -> p -> p
forall a. Predicatory a => a -> a -> a
`also` Pred p b
s b
b
pt :: (a -> b) -> PT p b a
pt :: forall a b p. (a -> b) -> PT p b a
pt a -> b
f Pred p b
p = Pred p b
p Pred p b -> (a -> b) -> a -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f
(?) :: (a -> b) -> a -> b
? :: forall a b. (a -> b) -> a -> b
(?) = (a -> b) -> a -> b
forall a b. (a -> b) -> a -> b
($)
infixr 8 ?
traced :: Show a => (a -> String) -> PT c a a
traced :: forall a c. Show a => (a -> String) -> PT c a a
traced a -> String
s Pred c a
p a
a = String -> c -> c
forall a. String -> a -> a
trace (a -> String
s a
a) (Pred c a
p a
a)
tracedShow :: Show a => PT c a a
tracedShow :: forall a c. Show a => PT c a a
tracedShow = (a -> String) -> PT c a a
forall a c. Show a => (a -> String) -> PT c a a
traced a -> String
forall a. Show a => a -> String
show
traceFailShow :: (Exceptional p, Predicatory p, Show a) => PT p a a
traceFailShow :: forall p a. (Exceptional p, Predicatory p, Show a) => PT p a a
traceFailShow = (a -> String) -> PT p a a
forall p a.
(Predicatory p, Exceptional p) =>
(a -> String) -> PT p a a
traceFail a -> String
forall a. Show a => a -> String
show
traceFail :: (Predicatory p, Exceptional p) => (a -> String) -> PT p a a
traceFail :: forall p a.
(Predicatory p, Exceptional p) =>
(a -> String) -> PT p a a
traceFail a -> String
s Pred p a
p a
a =
p -> IO () -> p
forall a. Exceptional a => a -> IO () -> a
assess (Pred p a
p a
a) (IO () -> p) -> IO () -> p
forall a b. (a -> b) -> a -> b
$ String -> IO ()
traceIO (a -> String
s a
a)
something :: Predicatory p => Pred p a
something :: forall a e. Predicatory a => e -> a
something = p -> a -> p
forall a b. a -> b -> a
const p
forall a. Predicatory a => a
continue
forced :: (Predicatory p, NFData a) => Pred p a
forced :: forall p a. (Predicatory p, NFData a) => Pred p a
forced a
a = a -> a
forall a. NFData a => a -> a
force a
a a -> p -> p
forall a b. a -> b -> b
`seq` p
forall a. Predicatory a => a
continue
equals :: (HasCallStack, Predicatory p, Eq a) => a -> Pred p a
equals :: forall p a. (HasCallStack, Predicatory p, Eq a) => a -> Pred p a
equals a
expected a
actual
| a
expected a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
actual = p
forall a. Predicatory a => a
continue
| Bool
otherwise = a -> Doc Any -> p
forall a v ann. (Predicatory a, HasCallStack) => v -> Doc ann -> a
forall v ann. HasCallStack => v -> Doc ann -> p
stop a
actual (Doc Any
"equal to" Doc Any -> Doc Any -> Doc Any
forall a. Semigroup a => a -> a -> a
<> Doc Any
forall ann. Doc ann
PP.softline Doc Any -> Doc Any -> Doc Any
forall a. Semigroup a => a -> a -> a
<> String -> Doc Any
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
PP.pretty (a -> String
forall a. a -> String
anythingToStringPretty a
expected))
satAll :: Predicatory p => [Pred p a] -> Pred p a
satAll :: forall p a. Predicatory p => [Pred p a] -> Pred p a
satAll [Pred p a]
xs a
a = (p -> p -> p) -> p -> [p] -> p
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr p -> p -> p
forall a. Predicatory a => a -> a -> a
also p
forall a. Predicatory a => a
continue ([p] -> p) -> [p] -> p
forall a b. (a -> b) -> a -> b
$ (Pred p a -> p) -> [Pred p a] -> [p]
forall a b. (a -> b) -> [a] -> [b]
map (Pred p a -> Pred p a
forall a b. (a -> b) -> a -> b
$ a
a) [Pred p a]
xs