-- | -- Module : Data.SubG -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} module Data.SubG ( subG , dropWhile , takeWhile , span , preAppend ) where import Prelude hiding (dropWhile, span, takeWhile) import qualified Data.Foldable as F import Data.Monoid infixr 1 %@, %^ class (Foldable t, Eq a, Eq (t a)) => InsertLeft t a where (%@) :: a -> t a -> t a -- infixr 1 (%^) :: t a -> t (t a) -> t (t a) instance (Eq a) => InsertLeft [] a where (%@) = (:) (%^) = (:) -- | Inspired by: 'https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.OldList.html#words' -- and Graham Hutton. A tutorial on the universality and expressiveness of fold. J. Functional Programming 9 (4): 355–372, July 1999. -- that is available at the URL: 'https://www.cs.nott.ac.uk/~pszgmh/fold.pdf'. subG :: (InsertLeft t a, Monoid (t a), Monoid (t (t a))) => t a -> t a -> t (t a) subG whspss xs = if F.null ts then mempty else w %^ subG whspss s'' where ts = dropWhile (`F.elem` whspss) xs (w, s'') = span (`F.notElem` whspss) ts dropWhile' :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> (t a, t a) dropWhile' p = F.foldr f v where f x (ys, xs) = (if p x then ys else x %@ xs, x %@ xs) v = (mempty,mempty) dropWhile :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> t a dropWhile p = fst . dropWhile' p span :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> (t a, t a) span p = fst . span' p span' :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> ((t a, t a), t a) span' p = F.foldr f v where f x ((ys, zs), xs) = (if p x then (x %@ ys, zs) else (mempty,x %@ xs), x %@ xs) v = ((mempty, mempty), mempty) takeWhile :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> t a takeWhile p = fst . takeWhile' p takeWhile' :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> (t a, t a) takeWhile' p = F.foldr f v where f x (ys,xs) = (if p x then x %@ ys else mempty, x %@ xs) v = (mempty,mempty) -- | Prepends and appends the given two first arguments to the third one. preAppend :: (InsertLeft t a, Monoid (t (t a))) => t a -> t (t a) -> t (t a) -> t (t a) preAppend ts uss tss = mconcat [ts %^ tss, uss] {-# INLINE preAppend #-}