{- |
The functions in this module process the list from the end.
They do not access elements at the beginning if not necessary.
You can apply the function only to finite lists.
Use these functions if the list is short and the test is expensive.
-}
module Data.List.Reverse.StrictSpine 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.StrictSpine as Rev
-- >>> import qualified Data.List.Match as Match
-- >>> import qualified Data.List as List
-- >>> import Data.Tuple.HT (mapFst, mapPair, swap)
-- >>>
-- >>> _suppressUnusedImportWarning :: (a -> Bool) -> [a] -> [a]
-- >>> _suppressUnusedImportWarning = Data.List.Reverse.StrictSpine.dropWhile


{- |
prop> forAllPredicates $ \p xs -> Rev.dropWhile p xs == reverse (List.dropWhile p (reverse xs))
prop> \x xs pad -> defined $ length $ Rev.dropWhile ((x::Char)/=) $ Match.replicate (pad::[()]) undefined ++ x:xs
-}
dropWhile :: (a -> Bool) -> [a] -> [a]
dropWhile :: forall a. (a -> Bool) -> [a] -> [a]
dropWhile a -> Bool
p =
   forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a
x [a]
xs -> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
xs Bool -> Bool -> Bool
&& a -> Bool
p a
x then [] else a
xforall a. a -> [a] -> [a]
:[a]
xs) []

{- |
prop> forAllPredicates $ \p xs -> Rev.takeWhile p xs == reverse (List.takeWhile p (reverse xs))
prop> \x xs pad -> defined $ Rev.takeWhile ((x::Char)/=) $ Match.replicate (pad::[()]) undefined ++ x:xs
-}
takeWhile :: (a -> Bool) -> [a] -> [a]
takeWhile :: forall a. (a -> Bool) -> [a] -> [a]
takeWhile a -> Bool
p =
   forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr
      (\a
x (Bool, [a])
xys ->
         (if forall a b. (a, b) -> a
fst (Bool, [a])
xys Bool -> Bool -> Bool
&& a -> Bool
p a
x then forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd (a
xforall a. a -> [a] -> [a]
:) else forall a c b. (a -> c) -> (a, b) -> (c, b)
mapFst (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 $ mapFst length $ Rev.span ((x::Char)/=) $ Match.replicate (pad::[()]) undefined ++ x:xs
-}
span :: (a -> Bool) -> [a] -> ([a], [a])
span :: forall a. (a -> Bool) -> [a] -> ([a], [a])
span a -> Bool
p =
   forall a b. (a, b) -> (a, b)
forcePair forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr
      (\a
x ([a], [a])
xys ->
         (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null (forall a b. (a, b) -> a
fst ([a], [a])
xys) Bool -> Bool -> Bool
&& a -> Bool
p a
x then forall b c a. (b -> c) -> (a, b) -> (a, c)
mapSnd else forall a c b. (a -> c) -> (a, b) -> (c, b)
mapFst) (a
xforall a. a -> [a] -> [a]
:) ([a], [a])
xys)
      ([], [])