{-# LANGUAGE ExistentialQuantification #-}

-- |
-- Module      : Test.Dwergaz
-- Description : A minimal testing library
-- Copyright   : (c) 2017-2023, Henry Till
-- License     : BSD3
-- Maintainer  : henrytill@gmail.com
-- Stability   : experimental
--
-- = Usage:
--
-- See the <https://github.com/henrytill/dwergaz/blob/master/tests/Main.hs tests> for a usage example.
--
module Test.Dwergaz
  ( Test(..)
  , Result
  , isPassed
  , runTest
  ) where


data Test
  = forall a. (Eq a, Show a) => Predicate String (a -> Bool)      a
  | forall a. (Eq a, Show a) => Expect    String (a -> a -> Bool) a a

data Result
  = Passed String
  | forall a. (Show a) => Failed String a a

instance Show Result where
  show :: Result -> String
show (Failed String
n a
e a
a) =
    String
"FAILED:   "     forall a. [a] -> [a] -> [a]
++ String
n      forall a. [a] -> [a] -> [a]
++
    String
"\nEXPECTED:   " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
e forall a. [a] -> [a] -> [a]
++
    String
"\nACTUAL:     " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
a
  show (Passed String
n) =
    String
"PASSED:   "     forall a. [a] -> [a] -> [a]
++ String
n

isPassed :: Result -> Bool
isPassed :: Result -> Bool
isPassed (Passed String
_) = Bool
True
isPassed Result
_          = Bool
False

runTest :: Test -> Result
runTest :: Test -> Result
runTest (Predicate String
n a -> Bool
p a
v) | a -> Bool
p a
v       = String -> Result
Passed String
n
                          | Bool
otherwise = forall a. Show a => String -> a -> a -> Result
Failed String
n Bool
True Bool
False
runTest (Expect String
n a -> a -> Bool
f a
e a
a)  | a -> a -> Bool
f a
e a
a     = String -> Result
Passed String
n
                          | Bool
otherwise = forall a. Show a => String -> a -> a -> Result
Failed String
n a
e a
a