-- |
-- Module      : Test.LeanCheck.Function.List
-- Copyright   : (c) 2015-2021 Rudy Matela
-- License     : 3-Clause BSD  (see the file LICENSE)
-- Maintainer  : Rudy Matela <rudy@matela.com.br>
--
-- This module is part of LeanCheck,
-- a simple enumerative property-based testing library.
--
-- This module exports functions to convert functions to lists of return
-- values and producing comparisons between functions.
module Test.LeanCheck.Function.List
  ( funToList
  , funToListMaybe
  , funToListEither
  , areEqualFor
  , compareFor
  )
where


import Test.LeanCheck
import Test.LeanCheck.Error (errorToNothing, errorToLeft)
import Data.Function (on)


-- | Converts a function to a list of result values
--   for each 'Listable' argument value.
--
-- > > list  ::  [Bool]
-- > [False,True]
-- > > funToList not
-- > [True,False]
--
-- > > list  ::  [(Bool,Bool)]
-- > [(False,False),(False,True),(True,False),(True,True)]
-- > > funToList $ uncurry (&&)
-- > [False,False,False,True]
--
-- This function may return an infinite list,
-- use 'take' as required.
--
-- > > take 10 $ list  ::  [Int]
-- > [0,1,-1,2,-2,3,-3,4,-4,5]
-- > > take 10 $ funToList (+1)  ::  [Int]
-- > [1,2,0,3,-1,4,-2,5,-3,6]
funToList :: Listable a => (a -> b) -> [b]
funToList :: (a -> b) -> [b]
funToList a -> b
f  =  (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map a -> b
f [a]
forall a. Listable a => [a]
list


-- | Converts a function to a list of 'Just' result values
--   or 'Nothing' on error.
--
-- > > take 6 $ funToListMaybe $ head :: [Maybe Int]
-- > [Nothing,Just 0,Just 0,Just 1,Just 0,Just 0]
--
-- This uses 'errorToNothing' and consequently 'unsafePerformIO'.
funToListMaybe :: Listable a => (a -> b) -> [Maybe b]
funToListMaybe :: (a -> b) -> [Maybe b]
funToListMaybe a -> b
f  =  (a -> Maybe b) -> [a] -> [Maybe b]
forall a b. (a -> b) -> [a] -> [b]
map (b -> Maybe b
forall a. a -> Maybe a
errorToNothing (b -> Maybe b) -> (a -> b) -> a -> Maybe b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f) [a]
forall a. Listable a => [a]
list


-- | Converts a function to a list of 'Just' result values
--   or 'Nothing' on error.
--
-- > > take 6 $ funToListEither $ head :: [Either String Int]
-- > [Left "Prelude.head: empty list",Right 0,Right 0,Right 1,Right 0,Right 0]
--
-- This uses 'errorToLeft' and consequently 'unsafePerformIO'.
funToListEither :: Listable a => (a -> b) -> [Either String b]
funToListEither :: (a -> b) -> [Either String b]
funToListEither a -> b
f  =  (a -> Either String b) -> [a] -> [Either String b]
forall a b. (a -> b) -> [a] -> [b]
map (b -> Either String b
forall a. a -> Either String a
errorToLeft (b -> Either String b) -> (a -> b) -> a -> Either String b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f) [a]
forall a. Listable a => [a]
list


-- | This function can be used to define an Eq instance for functions based on
--   testing and equality of returned values, like so:
--
-- > instance (Listable a, Eq b) => Eq (a -> b) where
-- >   (==)  =  areEqualFor 12
--
-- This catches errors and undefined values and treats them as equal.
areEqualFor :: (Listable a, Eq b) => Int -> (a -> b) -> (a -> b) -> Bool
areEqualFor :: Int -> (a -> b) -> (a -> b) -> Bool
areEqualFor Int
n  =  [Maybe b] -> [Maybe b] -> Bool
forall a. Eq a => a -> a -> Bool
(==) ([Maybe b] -> [Maybe b] -> Bool)
-> ((a -> b) -> [Maybe b]) -> (a -> b) -> (a -> b) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Int -> [Maybe b] -> [Maybe b]
forall a. Int -> [a] -> [a]
take Int
n ([Maybe b] -> [Maybe b])
-> ((a -> b) -> [Maybe b]) -> (a -> b) -> [Maybe b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> [Maybe b]
forall a b. Listable a => (a -> b) -> [Maybe b]
funToListMaybe)


-- | This function can be used to define an Ord instance for functions based on
--   testing and ordering of returned values, like so:
--
-- > instance (Listable a, Ord b) => Ord (a -> b) where
-- >   compare  =  compareFor 12
--
-- This catches errors and undefined values and treats them as equal.
compareFor :: (Listable a, Ord b) => Int -> (a -> b) -> (a -> b) -> Ordering
compareFor :: Int -> (a -> b) -> (a -> b) -> Ordering
compareFor Int
n  =  [Maybe b] -> [Maybe b] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ([Maybe b] -> [Maybe b] -> Ordering)
-> ((a -> b) -> [Maybe b]) -> (a -> b) -> (a -> b) -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Int -> [Maybe b] -> [Maybe b]
forall a. Int -> [a] -> [a]
take Int
n ([Maybe b] -> [Maybe b])
-> ((a -> b) -> [Maybe b]) -> (a -> b) -> [Maybe b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> [Maybe b]
forall a b. Listable a => (a -> b) -> [Maybe b]
funToListMaybe)