{-# LANGUAGE RankNTypes #-} module Signet.Unstable.Type.Test where import qualified Control.Monad as Monad import qualified Data.Void as Void import qualified GHC.Stack as Stack data Test spec = MkTest { forall (spec :: * -> *). Test spec -> HasCallStack => String -> IO Void assertFailure :: (Stack.HasCallStack) => String -> IO Void.Void, forall (spec :: * -> *). Test spec -> String -> spec () -> spec () describe :: String -> spec () -> spec (), forall (spec :: * -> *). Test spec -> String -> IO () -> spec () it :: String -> IO () -> spec () } assertEq :: (Stack.HasCallStack, Eq a, Show a) => Test tree -> a -> a -> IO () assertEq :: forall a (tree :: * -> *). (HasCallStack, Eq a, Show a) => Test tree -> a -> a -> IO () assertEq Test tree test a expected a actual = Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () Monad.when (a expected a -> a -> Bool forall a. Eq a => a -> a -> Bool /= a actual) (IO () -> IO ()) -> (String -> IO ()) -> String -> IO () forall b c a. (b -> c) -> (a -> b) -> a -> c . IO Void -> IO () forall (f :: * -> *) a. Functor f => f a -> f () Monad.void (IO Void -> IO ()) -> (String -> IO Void) -> String -> IO () forall b c a. (b -> c) -> (a -> b) -> a -> c . Test tree -> HasCallStack => String -> IO Void forall (spec :: * -> *). Test spec -> HasCallStack => String -> IO Void assertFailure Test tree test (String -> IO ()) -> String -> IO () forall a b. (a -> b) -> a -> b $ String "expected " String -> String -> String forall a. Semigroup a => a -> a -> a <> a -> String forall a. Show a => a -> String show a expected String -> String -> String forall a. Semigroup a => a -> a -> a <> String " but got " String -> String -> String forall a. Semigroup a => a -> a -> a <> a -> String forall a. Show a => a -> String show a actual