-- | -- Module : Data.SubG -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Some extension to the 'F.Foldable' and 'Monoid' classes. Introduces a new class 'InsertLeft' -- the class of types of values that can be inserted from the left -- to the 'F.Foldable' structure that is simultaneously the data that is also the 'Monoid' instance. {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} module Data.SubG ( InsertLeft(..) , subG , take , takeFromEnd , reverseTake , reverseTakeFromEnd , drop , dropFromEnd , reverseDrop , reverseDropFromEnd , takeWhile , dropWhile , span , preAppend , safeHead , safeTail , safeInit , safeLast ) where import Prelude hiding (dropWhile, span, takeWhile,drop,take,splitAt) import qualified Data.Foldable as F import Data.Monoid infixr 1 %@, %^ -- | Some extension to the 'F.Foldable' and 'Monoid' classes. class (F.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. Is similar to the 'Prelude.words' but operates on more general -- structures an allows more control. 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 -- | Inspired by: 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. 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) -- | Inspired by: 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. dropWhile :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> t a dropWhile p = fst . dropWhile' p -- | Inspired by: 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. span :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> (t a, t a) span p = fst . span' p -- | Inspired by: 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. 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) -- | Inspired by: 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. takeWhile :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> t a takeWhile p = fst . takeWhile' p -- | Inspired by: 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. 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 #-} ------------------------------------------------------------------------------------- -- | Inspired by: 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. -- Takes the first argument quantity from the right end of the structure preserving the order. takeFromEnd :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a takeFromEnd n = (\(xs,_,_) -> xs) . F.foldr f v where v = (mempty,0,n) f x (zs,k,n) | k < n = (x %@ zs,k + 1,n) | otherwise = (zs,k,n) -- | Inspired by: 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. -- Takes the specified quantity from the right end of the structure and then reverses the result. reverseTakeFromEnd :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a reverseTakeFromEnd n = (\(xs,_,_) -> xs) . F.foldr f v where v = (mempty,0,n) f x (zs,k,n) | k < n = (zs `mappend` (x %@ mempty),k + 1,n) | otherwise = (zs,k,n) -- | Inspired by: 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. -- Is analogous to the taking the specified quantity from the structure and then reversing the result. Uses strict variant of the foldl, so is -- not suitable for large amounts of data. reverseTake :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a reverseTake n = (\(xs,_,_) -> xs) . F.foldl' f v where v = (mempty,0,n) f (zs,k,n) x | k < n = (x %@ zs,k + 1,n) | otherwise = (zs,k,n) -- | Inspired by: 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. Uses strict variant of the foldl, so is -- strict and the data must be finite. take :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a take n = (\(xs,_,_) -> xs) . F.foldl' f v where v = (mempty,0,n) f (zs,k,n) x | k < n = (zs `mappend` (x %@ mempty),k + 1,n) | otherwise = (zs,k,n) -- | Inspired by: 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. -- Is analogous to the dropping the specified quantity from the structure and then reversing the result. Uses strict variant of the foldl, so is -- strict and the data must be finite. reverseDrop :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a reverseDrop n = (\(xs,_,_) -> xs) . F.foldl' f v where v = (mempty,0,n) f (zs,k,n) x | k < n = (mempty,k + 1,n) | otherwise = (x %@ zs,k,n) -- | Inspired by: 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. -- Drops the first argument quantity from the right end of the structure and returns the result preserving the order. dropFromEnd :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a dropFromEnd n = (\(xs,_,_) -> xs) . F.foldr f v where v = (mempty,0,n) f x (zs,k,n) | k < n = (mempty,k + 1,n) | otherwise = (x %@ zs,k,n) -- | Inspired by: 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. -- Drops the specified quantity from the right end of the structure and then reverses the result. reverseDropFromEnd :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a reverseDropFromEnd n = (\(xs,_,_) -> xs) . F.foldr f v where v = (mempty,0,n) f x (zs,k,n) | k < n = (mempty,k + 1,n) | otherwise = (zs `mappend` (x %@ mempty),k,n) -- | Inspired by: 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. Uses strict variant of the foldl, so is -- strict and the data must be finite. drop :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a drop n = (\(xs,_,_) -> xs) . F.foldl' f v where v = (mempty,0,n) f (zs,k,n) x | k < n = (mempty,k + 1,n) | otherwise = (zs `mappend` (x %@ mempty),k,n) -- | Inspired by: 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. Uses strict variant of the foldl, so is -- strict and the data must be finite. splitAt :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> (t a, t a) splitAt n = (\(x,y,_,_) -> (x,y)) . F.foldl' f v where v = (mempty,mempty,0,n) f (zs,ts,k,n) x | k < n = (zs `mappend` (x %@ mempty),mempty,k + 1,n) | otherwise = (zs,ts `mappend` (x %@ mempty),k + 1,n) -- | If a structure is empty, just returns 'Nothing'. safeHead :: (Foldable t) => t a -> Maybe a safeHead = F.find (const True) -- | If the structure is empty, just returns itself. Uses strict variant of the foldl, so is -- strict and the data must be finite. safeTail :: (InsertLeft t a, Monoid (t a)) => t a -> t a safeTail = drop 1 -- | If the structure is empty, just returns itself. safeInit :: (InsertLeft t a, Monoid (t a)) => t a -> t a safeInit = dropFromEnd 1 -- | If the structure is empty, just returns 'Nothing'. safeLast :: (InsertLeft t a, Monoid (t a)) => t a -> Maybe a safeLast = F.find (const True) . takeFromEnd 1