{- |
The functions in this module process the list formally from the end.
Actually they traverse the list from the start and check every element.
This way they are strict in the elements and lazy in the list spline.
Thus you can apply them to infinite lists.
Use these functions if the list is long or the test is cheap.
-}
module Data.List.Reverse.StrictElement where

import Data.Tuple.HT (mapFst, mapSnd, forcePair, )

import Prelude hiding (dropWhile, takeWhile, span, )


-- $setup
-- >>> import Test.Utility (forAllPredicates, defined)
-- >>> import qualified Data.List.Reverse.StrictElement as Rev
-- >>> import qualified Data.List.Match as Match
-- >>> import qualified Data.List as List
-- >>> import Data.Tuple.HT (mapPair, swap)
-- >>>
-- >>> _suppressUnusedImportWarning :: (a -> Bool) -> [a] -> [a]
-- >>> _suppressUnusedImportWarning = Data.List.Reverse.StrictElement.dropWhile


{- |
Remove the longest suffix of elements satisfying p.
In contrast to @reverse . dropWhile p . reverse@
this works for infinite lists, too.

prop> forAllPredicates $ \p xs -> Rev.dropWhile p xs == reverse (List.dropWhile p (reverse xs))
prop> \x xs pad -> defined $ Match.take (pad::[()]) $ Rev.dropWhile ((x::Char)/=) $ cycle $ x:xs
-}
dropWhile :: (a -> Bool) -> [a] -> [a]
dropWhile :: (a -> Bool) -> [a] -> [a]
dropWhile a -> Bool
p =
   (a -> [a] -> [a]) -> [a] -> [a] -> [a]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a
x [a]
xs -> if a -> Bool
p a
x Bool -> Bool -> Bool
&& [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
xs then [] else a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
xs) []

{- |
Alternative version of @reverse . takeWhile p . reverse@.

prop> forAllPredicates $ \p xs -> Rev.takeWhile p xs == reverse (List.takeWhile p (reverse xs))
-}
takeWhile :: (a -> Bool) -> [a] -> [a]
takeWhile :: (a -> Bool) -> [a] -> [a]
takeWhile a -> Bool
p =
   (Bool, [a]) -> [a]
forall a b. (a, b) -> b
snd ((Bool, [a]) -> [a]) -> ([a] -> (Bool, [a])) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   (a -> (Bool, [a]) -> (Bool, [a]))
-> (Bool, [a]) -> [a] -> (Bool, [a])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr
      (\a
x (Bool, [a])
xys ->
         (if a -> Bool
p a
x Bool -> Bool -> Bool
&& (Bool, [a]) -> Bool
forall a b. (a, b) -> a
fst (Bool, [a])
xys then ([a] -> [a]) -> (Bool, [a]) -> (Bool, [a])
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:) else (Bool -> Bool) -> (Bool, [a]) -> (Bool, [a])
forall a c b. (a -> c) -> (a, b) -> (c, b)
mapFst (Bool -> Bool -> Bool
forall a b. a -> b -> a
const Bool
False)) (Bool, [a])
xys)
      (Bool
True, [])

{- |
prop> forAllPredicates $ \p xs -> Rev.span p xs == swap (mapPair (reverse, reverse) (List.span p (reverse xs)))
prop> forAllPredicates $ \p xs -> Rev.span p xs == (Rev.dropWhile p xs, Rev.takeWhile p xs)
prop> \x xs pad -> defined $ Match.take (pad::[()]) $ fst $ Rev.span ((x::Char)/=) $ cycle $ x:xs
-}
span :: (a -> Bool) -> [a] -> ([a], [a])
span :: (a -> Bool) -> [a] -> ([a], [a])
span a -> Bool
p =
   ([a], [a]) -> ([a], [a])
forall a b. (a, b) -> (a, b)
forcePair (([a], [a]) -> ([a], [a]))
-> ([a] -> ([a], [a])) -> [a] -> ([a], [a])
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   (a -> ([a], [a]) -> ([a], [a])) -> ([a], [a]) -> [a] -> ([a], [a])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr
      (\a
x ([a], [a])
xys ->
         (if a -> Bool
p a
x Bool -> Bool -> Bool
&& [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (([a], [a]) -> [a]
forall a b. (a, b) -> a
fst ([a], [a])
xys) then ([a] -> [a]) -> ([a], [a]) -> ([a], [a])
forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd else ([a] -> [a]) -> ([a], [a]) -> ([a], [a])
forall a c b. (a -> c) -> (a, b) -> (c, b)
mapFst) (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:) ([a], [a])
xys)
      ([], [])