{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
#if __GLASGOW_HASKELL__ < 806
#define HADDOCK --
#else
#define HADDOCK -- ^
#endif
module Polysemy.Law
( Law (..)
, runLaw
, MakeLaw (..)
, Citizen (..)
, printf
, module Test.QuickCheck
) where
import Control.Arrow (first)
import Data.Char
import Polysemy
import Test.QuickCheck
class Citizen r a | r -> a where
getCitizen :: r -> r -> Gen ([String], (a, a))
instance {-# OVERLAPPING #-} Citizen (Sem r a -> b) (Sem r a -> b) where
getCitizen r1 r2 = pure ([], (r1, r2))
instance Citizen (Sem r a) (Sem r a) where
getCitizen r1 r2 = pure ([], (r1, r2))
instance (Arbitrary a, Show a, Citizen b r) => Citizen (a -> b) r where
getCitizen f1 f2 = do
a <- arbitrary
first (show a :) <$> getCitizen (f1 a) (f2 a)
data Law e r where
Law
:: ( Eq a
, Show a
, Citizen i12n (Sem r x -> a)
, Citizen res (Sem (e ': r) x)
)
=> i12n
HADDOCK An interpretation from @'Sem' r x@ down to a pure value. This is
-> String
HADDOCK A string representation of the left-hand of the rule. This is
-> res
HADDOCK The left-hand rule. This thing may be of type @'Sem' (e ': r) x@,
-> String
HADDOCK A string representation of the right-hand of the rule. This is
-> res
HADDOCK The right-hand rule. This thing may be of type @'Sem' (e ': r) x@,
-> Law e r
LawIO
:: ( Eq a
, Show a
, Citizen i12n (Sem r x -> IO a)
, Citizen res (Sem (e ': r) x)
)
=> i12n
HADDOCK An interpretation from @'Sem' r x@ down to an 'IO' value. This is
-> String
HADDOCK A string representation of the left-hand of the rule. This is
-> res
HADDOCK The left-hand rule. This thing may be of type @'Sem' (e ': r) x@,
-> String
HADDOCK A string representation of the right-hand of the rule. This is
-> res
HADDOCK The right-hand rule. This thing may be of type @'Sem' (e ': r) x@,
-> Law e r
class MakeLaw e r where
mkLaw
:: (Eq a, Show a, Citizen res (Sem (e ': r) a))
=> String
-> res
-> String
-> res
-> Law e r
instance MakeLaw e '[] where
mkLaw = Law run
instance MakeLaw e '[Embed IO] where
mkLaw = LawIO runM
runLaw :: InterpreterFor e r -> Law e r -> Property
runLaw i12n (Law finish str1 a str2 b) = property $ do
(_, (lower, _)) <- getCitizen finish finish
(args, (ma, mb)) <- getCitizen a b
let run_it = lower . i12n
a' = run_it ma
b' = run_it mb
pure $
counterexample
(mkCounterexampleString str1 a' str2 b' args)
(a' == b')
runLaw i12n (LawIO finish str1 a str2 b) = property $ do
(_, (lower, _)) <- getCitizen finish finish
(args, (ma, mb)) <- getCitizen a b
let run_it = lower . i12n
pure $ ioProperty $ do
a' <- run_it ma
b' <- run_it mb
pure $
counterexample
(mkCounterexampleString str1 a' str2 b' args)
(a' == b')
mkCounterexampleString
:: Show a
=> String
-> a
-> String
-> a
-> [String]
-> String
mkCounterexampleString str1 a str2 b args =
mconcat
[ printf str1 args , " (result: " , show a , ")\n /= \n"
, printf str2 args , " (result: " , show b , ")"
]
printf :: String -> [String] -> String
printf str args = splitArgs str
where
splitArgs :: String -> String
splitArgs s =
case break (== '%') s of
(as, "") -> as
(as, _ : b : bs)
| isDigit b
, let d = read [b] - 1
, d < length args
-> as ++ (args !! d) ++ splitArgs bs
(as, _ : bs) -> as ++ "%" ++ splitArgs bs