module Data.List.Reverse.StrictSpine where
import Data.Tuple.HT (mapFst, mapSnd, forcePair, )
import Prelude hiding (dropWhile, takeWhile, span, )
dropWhile :: (a -> Bool) -> [a] -> [a]
dropWhile p =
foldr (\x xs -> if null xs && p x then [] else x:xs) []
takeWhile :: (a -> Bool) -> [a] -> [a]
takeWhile p =
snd .
foldr
(\x xys ->
(if fst xys && p x then mapSnd (x:) else mapFst (const False)) xys)
(True, [])
span :: (a -> Bool) -> [a] -> ([a], [a])
span p =
forcePair .
foldr
(\x xys ->
(if null (fst xys) && p x then mapSnd else mapFst) (x:) xys)
([], [])