{- | Functions that cope both with plain and non-empty structures. -} module Data.NonEmpty.Mixed ( module Data.NonEmpty.Mixed, Priv.appendRight) where import qualified Data.NonEmpty.Class as C import qualified Data.NonEmptyPrivate as Priv import qualified Data.NonEmpty as NonEmpty import Data.Foldable (Foldable, foldr, ) import Prelude hiding (foldr, ) groupBy :: (Foldable f) => (a -> a -> Bool) -> f a -> [NonEmpty.T [] a] groupBy p = foldr (\x0 yt -> let (xr,yr) = case yt of NonEmpty.Cons x1 xs : ys -> if p x0 x1 then (x1:xs,ys) else ([],yt) [] -> ([],yt) in NonEmpty.Cons x0 xr : yr) [] segmentBefore :: (Foldable f) => (a -> Bool) -> f a -> ([a], [NonEmpty.T [] a]) segmentBefore p = foldr (\ x ys -> if p x then ([], NonEmpty.Cons x (fst ys) : snd ys) else (x : fst ys, snd ys)) ([],[]) scanl :: (a -> b -> a) -> a -> [b] -> NonEmpty.T [] a scanl f = let go a bt = NonEmpty.Cons a $ case bt of [] -> [] b:bs -> NonEmpty.flatten $ go (f a b) bs in go {- Fusable and generic, but not as lazy as 'scanl'. -} genericScanl :: (Foldable f) => (a -> b -> a) -> a -> f b -> NonEmpty.T [] a genericScanl f a0 xs = NonEmpty.force $ foldr (\ b go a -> NonEmpty.Cons a $ NonEmpty.flatten $ go $ f a b) (\ a -> NonEmpty.Cons a []) xs a0 insertBy :: (C.Sort f) => (a -> a -> Ordering) -> a -> f a -> NonEmpty.T f a insertBy f y xs = uncurry NonEmpty.Cons $ C.insertBy f y xs insert :: (Ord a, C.Sort f) => a -> f a -> NonEmpty.T f a insert = insertBy compare infixl 5 `appendLeft` appendLeft :: (C.Append f, C.View f, C.Cons f) => f a -> NonEmpty.T f a -> NonEmpty.T f a appendLeft xt yt = NonEmpty.force $ case C.viewL xt of Nothing -> yt Just (x,xs) -> NonEmpty.Cons x $ C.append xs $ NonEmpty.flatten yt tails :: (C.View f, C.Empty f) => f a -> NonEmpty.T [] (f a) tails xt = NonEmpty.force $ case C.viewL xt of Nothing -> NonEmpty.Cons C.empty [] Just (_, xs) -> NonEmpty.cons xt $ tails xs inits :: (C.View f, C.Cons f, C.Empty f) => f a -> NonEmpty.T [] (f a) inits xt = NonEmpty.Cons C.empty $ case C.viewL xt of Nothing -> [] Just (x,xs) -> map (C.cons x) $ NonEmpty.flatten $ inits xs