-- |
-- Module      : Test.Speculate.Utils.Tiers
-- Copyright   : (c) 2016-2024 Rudy Matela
-- License     : 3-Clause BSD  (see the file LICENSE)
-- Maintainer  : Rudy Matela <rudy@matela.com.br>
--
-- This module is part of Speculate.
--
-- Utilities for manipulating tiers of values (of the 'Listable' typeclass).
module Test.Speculate.Utils.Tiers
  ( productsList
  , mapTMaybe
  , uptoT
  , filterTS
  , discardTS
  )
where

import Test.LeanCheck
import Data.Maybe (mapMaybe)

productsList :: [[a]] -> [[a]]
productsList :: forall a. [[a]] -> [[a]]
productsList = [[[a]]] -> [[a]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[[a]]] -> [[a]]) -> ([[a]] -> [[[a]]]) -> [[a]] -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[a]]] -> [[[a]]]
forall a. [[[a]]] -> [[[a]]]
products ([[[a]]] -> [[[a]]]) -> ([[a]] -> [[[a]]]) -> [[a]] -> [[[a]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a] -> [[a]]) -> [[a]] -> [[[a]]]
forall a b. (a -> b) -> [a] -> [b]
map [a] -> [[a]]
forall a. [a] -> [[a]]
toTiers

mapTMaybe :: (a -> Maybe b) -> [[a]] -> [[b]]
mapTMaybe :: forall a b. (a -> Maybe b) -> [[a]] -> [[b]]
mapTMaybe a -> Maybe b
f = ([a] -> [b]) -> [[a]] -> [[b]]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> Maybe b) -> [a] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe a -> Maybe b
f)

uptoT :: Int -> [[a]] -> [a]
uptoT :: forall a. Int -> [[a]] -> [a]
uptoT Int
sz = [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[a]] -> [a]) -> ([[a]] -> [[a]]) -> [[a]] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [[a]] -> [[a]]
forall a. Int -> [a] -> [a]
take Int
sz

-- this passes the size of the a to the selecting function
filterTS :: (Int -> a -> Bool) -> [[a]] -> [[a]]
filterTS :: forall a. (Int -> a -> Bool) -> [[a]] -> [[a]]
filterTS Int -> a -> Bool
p = Int -> [[a]] -> [[a]]
fts Int
0
  where
  fts :: Int -> [[a]] -> [[a]]
fts Int
n []       = []
  fts Int
n ([a]
xs:[[a]]
xss) = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> a -> Bool
p Int
n) [a]
xs [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: Int -> [[a]] -> [[a]]
fts (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [[a]]
xss

discardTS :: (Int -> a -> Bool) -> [[a]] -> [[a]]
discardTS :: forall a. (Int -> a -> Bool) -> [[a]] -> [[a]]
discardTS Int -> a -> Bool
p = (Int -> a -> Bool) -> [[a]] -> [[a]]
forall a. (Int -> a -> Bool) -> [[a]] -> [[a]]
filterTS ((Bool -> Bool
not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((a -> Bool) -> a -> Bool)
-> (Int -> a -> Bool) -> Int -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Bool
p)