{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}

#if HAVE_QUANTIFIED_CONSTRAINTS
{-# LANGUAGE QuantifiedConstraints #-}
#endif

{-# OPTIONS_GHC -Wall #-}

module Test.QuickCheck.Classes.Functor
  (
#if HAVE_UNARY_LAWS
    functorLaws
#endif
  ) where

import Data.Functor
import Test.QuickCheck hiding ((.&.))
#if HAVE_UNARY_LAWS
import Test.QuickCheck.Arbitrary (Arbitrary1(..))
import Data.Functor.Classes (Eq1,Show1)
#endif
import Test.QuickCheck.Property (Property)

import Test.QuickCheck.Classes.Internal

#if HAVE_UNARY_LAWS

-- | Tests the following functor properties:
--
-- [/Identity/]
--   @'fmap' 'id' ≡ 'id'@
-- [/Composition/]
--   @'fmap' (f '.' g) ≡ 'fmap' f '.' 'fmap' g@
-- [/Const/]
--   @('<$') ≡ 'fmap' 'const'@
functorLaws ::
#if HAVE_QUANTIFIED_CONSTRAINTS
  (Functor f, forall a. Eq a => Eq (f a), forall a. Show a => Show (f a), forall a. Arbitrary a => Arbitrary (f a))
#else
  (Functor f, Eq1 f, Show1 f, Arbitrary1 f)
#endif
  => proxy f
  -> Laws
functorLaws :: proxy f -> Laws
functorLaws proxy f
p = String -> [(String, Property)] -> Laws
Laws String
"Functor"
  [ (String
"Identity", proxy f -> Property
forall (proxy :: (* -> *) -> *) (f :: * -> *).
(Functor f, forall a. Eq a => Eq (f a),
 forall a. Show a => Show (f a),
 forall a. Arbitrary a => Arbitrary (f a)) =>
proxy f -> Property
functorIdentity proxy f
p)
  , (String
"Composition", proxy f -> Property
forall (proxy :: (* -> *) -> *) (f :: * -> *).
(Functor f, forall a. Eq a => Eq (f a),
 forall a. Show a => Show (f a),
 forall a. Arbitrary a => Arbitrary (f a)) =>
proxy f -> Property
functorComposition proxy f
p)
  , (String
"Const", proxy f -> Property
forall (proxy :: (* -> *) -> *) (f :: * -> *).
(Functor f, forall a. Eq a => Eq (f a),
 forall a. Show a => Show (f a),
 forall a. Arbitrary a => Arbitrary (f a)) =>
proxy f -> Property
functorConst proxy f
p)
  ]

functorIdentity :: forall proxy f.
#if HAVE_QUANTIFIED_CONSTRAINTS
  (Functor f, forall a. Eq a => Eq (f a), forall a. Show a => Show (f a), forall a. Arbitrary a => Arbitrary (f a))
#else
  (Functor f, Eq1 f, Show1 f, Arbitrary1 f)
#endif
  => proxy f -> Property
functorIdentity :: proxy f -> Property
functorIdentity proxy f
_ = (Apply f Integer -> Bool) -> Property
forall prop. Testable prop => prop -> Property
property ((Apply f Integer -> Bool) -> Property)
-> (Apply f Integer -> Bool) -> Property
forall a b. (a -> b) -> a -> b
$ \(Apply (f Integer
a :: f Integer)) -> f Integer -> f Integer -> Bool
forall (f :: * -> *) a.
(forall x. Eq x => Eq (f x), Eq a) =>
f a -> f a -> Bool
eq1 ((Integer -> Integer) -> f Integer -> f Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> Integer
forall a. a -> a
id f Integer
a) f Integer
a

functorComposition :: forall proxy f.
#if HAVE_QUANTIFIED_CONSTRAINTS
  (Functor f, forall a. Eq a => Eq (f a), forall a. Show a => Show (f a), forall a. Arbitrary a => Arbitrary (f a))
#else
  (Functor f, Eq1 f, Show1 f, Arbitrary1 f)
#endif
  => proxy f -> Property
functorComposition :: proxy f -> Property
functorComposition proxy f
_ = (Apply f Integer -> Bool) -> Property
forall prop. Testable prop => prop -> Property
property ((Apply f Integer -> Bool) -> Property)
-> (Apply f Integer -> Bool) -> Property
forall a b. (a -> b) -> a -> b
$ \(Apply (f Integer
a :: f Integer)) ->
  f (Bool, Either Ordering Integer)
-> f (Bool, Either Ordering Integer) -> Bool
forall (f :: * -> *) a.
(forall x. Eq x => Eq (f x), Eq a) =>
f a -> f a -> Bool
eq1 (((Integer, Integer) -> (Bool, Either Ordering Integer))
-> f (Integer, Integer) -> f (Bool, Either Ordering Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer, Integer) -> (Bool, Either Ordering Integer)
func2 ((Integer -> (Integer, Integer))
-> f Integer -> f (Integer, Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> (Integer, Integer)
func1 f Integer
a)) ((Integer -> (Bool, Either Ordering Integer))
-> f Integer -> f (Bool, Either Ordering Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Integer, Integer) -> (Bool, Either Ordering Integer)
func2 ((Integer, Integer) -> (Bool, Either Ordering Integer))
-> (Integer -> (Integer, Integer))
-> Integer
-> (Bool, Either Ordering Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> (Integer, Integer)
func1) f Integer
a)

functorConst :: forall proxy f.
#if HAVE_QUANTIFIED_CONSTRAINTS
  (Functor f, forall a. Eq a => Eq (f a), forall a. Show a => Show (f a), forall a. Arbitrary a => Arbitrary (f a))
#else
  (Functor f, Eq1 f, Show1 f, Arbitrary1 f)
#endif
  => proxy f -> Property
functorConst :: proxy f -> Property
functorConst proxy f
_ = (Apply f Integer -> Bool) -> Property
forall prop. Testable prop => prop -> Property
property ((Apply f Integer -> Bool) -> Property)
-> (Apply f Integer -> Bool) -> Property
forall a b. (a -> b) -> a -> b
$ \(Apply (f Integer
a :: f Integer)) ->
  f Char -> f Char -> Bool
forall (f :: * -> *) a.
(forall x. Eq x => Eq (f x), Eq a) =>
f a -> f a -> Bool
eq1 ((Integer -> Char) -> f Integer -> f Char
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Char -> Integer -> Char
forall a b. a -> b -> a
const Char
'X') f Integer
a) (Char
'X' Char -> f Integer -> f Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ f Integer
a)

#endif