-- |
-- 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
  , takeG
  , takeFromEndG
  , reverseTakeG
  , reverseTakeFromEndG
  , dropG
  , dropFromEndG
  , reverseDropG
  , reverseDropFromEndG
  , takeWhile
  , dropWhile
  , span
  , splitAtG
  , splitAtEndG
  , preAppend
  , safeHeadG
  , safeTailG
  , safeInitG
  , safeLastG
  , mapG
  , filterG
  , partitionG
) where

import Prelude hiding (dropWhile, span, takeWhile)
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
  %@ :: a -> [a] -> [a]
(%@) = (:)
  %^ :: [a] -> [[a]] -> [[a]]
(%^) = (:)

-- | 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 :: t a -> t a -> t (t a)
subG t a
whspss t a
xs = if t a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
F.null t a
ts then t (t a)
forall a. Monoid a => a
mempty else t a
w t a -> t (t a) -> t (t a)
forall (t :: * -> *) a. InsertLeft t a => t a -> t (t a) -> t (t a)
%^ t a -> t a -> t (t a)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a), Monoid (t (t a))) =>
t a -> t a -> t (t a)
subG t a
whspss t a
s''
     where ts :: t a
ts = (a -> Bool) -> t a -> t a
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
dropWhile (a -> t a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`F.elem` t a
whspss) t a
xs
           (t a
w, t a
s'') = (a -> Bool) -> t a -> (t a, t a)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> (t a, t a)
span (a -> t a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`F.notElem` t a
whspss) t a
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' :: (a -> Bool) -> t a -> (t a, t a)
dropWhile' a -> Bool
p = (a -> (t a, t a) -> (t a, t a)) -> (t a, t a) -> t a -> (t a, t a)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> (t a, t a) -> (t a, t a)
forall (t :: * -> *).
InsertLeft t a =>
a -> (t a, t a) -> (t a, t a)
f (t a, t a)
v
  where f :: a -> (t a, t a) -> (t a, t a)
f a
x (t a
ys, t a
xs) = (if a -> Bool
p a
x then t a
ys else a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
xs, a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
xs)
        v :: (t a, t a)
v = (t a
forall a. Monoid a => a
mempty,t a
forall a. Monoid a => a
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 :: (a -> Bool) -> t a -> t a
dropWhile a -> Bool
p = (t a, t a) -> t a
forall a b. (a, b) -> a
fst ((t a, t a) -> t a) -> (t a -> (t a, t a)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> t a -> (t a, t a)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> (t a, t a)
dropWhile' a -> Bool
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 :: (a -> Bool) -> t a -> (t a, t a)
span a -> Bool
p = ((t a, t a), t a) -> (t a, t a)
forall a b. (a, b) -> a
fst (((t a, t a), t a) -> (t a, t a))
-> (t a -> ((t a, t a), t a)) -> t a -> (t a, t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> t a -> ((t a, t a), t a)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> ((t a, t a), t a)
span' a -> Bool
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' :: (a -> Bool) -> t a -> ((t a, t a), t a)
span' a -> Bool
p = (a -> ((t a, t a), t a) -> ((t a, t a), t a))
-> ((t a, t a), t a) -> t a -> ((t a, t a), t a)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> ((t a, t a), t a) -> ((t a, t a), t a)
forall (t :: * -> *) (t :: * -> *).
(Monoid (t a), InsertLeft t a, InsertLeft t a) =>
a -> ((t a, t a), t a) -> ((t a, t a), t a)
f ((t a, t a), t a)
v
  where f :: a -> ((t a, t a), t a) -> ((t a, t a), t a)
f a
x ((t a
ys, t a
zs), t a
xs) = (if a -> Bool
p a
x then (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
ys, t a
zs) else (t a
forall a. Monoid a => a
mempty,a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
xs), a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
xs)
        v :: ((t a, t a), t a)
v = ((t a
forall a. Monoid a => a
mempty, t a
forall a. Monoid a => a
mempty), t a
forall a. Monoid a => a
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 :: (a -> Bool) -> t a -> t a
takeWhile a -> Bool
p = (t a, t a) -> t a
forall a b. (a, b) -> a
fst ((t a, t a) -> t a) -> (t a -> (t a, t a)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> t a -> (t a, t a)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> (t a, t a)
takeWhile' a -> Bool
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' :: (a -> Bool) -> t a -> (t a, t a)
takeWhile' a -> Bool
p = (a -> (t a, t a) -> (t a, t a)) -> (t a, t a) -> t a -> (t a, t a)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> (t a, t a) -> (t a, t a)
forall (t :: * -> *) (t :: * -> *).
(Monoid (t a), InsertLeft t a, InsertLeft t a) =>
a -> (t a, t a) -> (t a, t a)
f (t a, t a)
v
  where f :: a -> (t a, t a) -> (t a, t a)
f a
x (t a
ys,t a
xs) = (if a -> Bool
p a
x then a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
ys else t a
forall a. Monoid a => a
mempty, a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
xs)
        v :: (t a, t a)
v = (t a
forall a. Monoid a => a
mempty,t a
forall a. Monoid a => a
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 :: t a -> t (t a) -> t (t a) -> t (t a)
preAppend t a
ts t (t a)
uss t (t a)
tss = [t (t a)] -> t (t a)
forall a. Monoid a => [a] -> a
mconcat [t a
ts t a -> t (t a) -> t (t a)
forall (t :: * -> *) a. InsertLeft t a => t a -> t (t a) -> t (t a)
%^ t (t a)
tss, t (t a)
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.
takeFromEndG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a
takeFromEndG :: b -> t a -> t a
takeFromEndG b
n = (\(t a
xs,b
_,b
_) -> t a
xs) ((t a, b, b) -> t a) -> (t a -> (t a, b, b)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (t a, b, b) -> (t a, b, b))
-> (t a, b, b) -> t a -> (t a, b, b)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> (t a, b, b) -> (t a, b, b)
forall c (t :: * -> *) a.
(Ord c, InsertLeft t a, Num c) =>
a -> (t a, c, c) -> (t a, c, c)
f (t a, b, b)
v
 where v :: (t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: a -> (t a, c, c) -> (t a, c, c)
f a
x (t a
zs,c
k,c
n)
        | c
k c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
n = (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
zs,c
k c -> c -> c
forall a. Num a => a -> a -> a
+ c
1,c
n)
        | Bool
otherwise = (t a
zs,c
k,c
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.
reverseTakeFromEndG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a
reverseTakeFromEndG :: b -> t a -> t a
reverseTakeFromEndG b
n = (\(t a
xs,b
_,b
_) -> t a
xs) ((t a, b, b) -> t a) -> (t a -> (t a, b, b)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (t a, b, b) -> (t a, b, b))
-> (t a, b, b) -> t a -> (t a, b, b)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> (t a, b, b) -> (t a, b, b)
forall c (t :: * -> *) a.
(Ord c, Monoid (t a), InsertLeft t a, Num c) =>
a -> (t a, c, c) -> (t a, c, c)
f (t a, b, b)
v
 where v :: (t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: a -> (t a, c, c) -> (t a, c, c)
f a
x (t a
zs,c
k,c
n)
        | c
k c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
n = (t a
zs t a -> t a -> t a
forall a. Monoid a => a -> a -> a
`mappend` (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
forall a. Monoid a => a
mempty),c
k c -> c -> c
forall a. Num a => a -> a -> a
+ c
1,c
n)
        | Bool
otherwise = (t a
zs,c
k,c
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.
reverseTakeG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a
reverseTakeG :: b -> t a -> t a
reverseTakeG b
n = (\(t a
xs,b
_,b
_) -> t a
xs) ((t a, b, b) -> t a) -> (t a -> (t a, b, b)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((t a, b, b) -> a -> (t a, b, b))
-> (t a, b, b) -> t a -> (t a, b, b)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' (t a, b, b) -> a -> (t a, b, b)
forall c (t :: * -> *) a.
(Ord c, InsertLeft t a, Num c) =>
(t a, c, c) -> a -> (t a, c, c)
f (t a, b, b)
v
 where v :: (t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: (t a, c, c) -> a -> (t a, c, c)
f (t a
zs,c
k,c
n) a
x
        | c
k c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
n = (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
zs,c
k c -> c -> c
forall a. Num a => a -> a -> a
+ c
1,c
n)
        | Bool
otherwise = (t a
zs,c
k,c
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.
takeG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a
takeG :: b -> t a -> t a
takeG b
n = (\(t a
xs,b
_,b
_) -> t a
xs) ((t a, b, b) -> t a) -> (t a -> (t a, b, b)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((t a, b, b) -> a -> (t a, b, b))
-> (t a, b, b) -> t a -> (t a, b, b)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' (t a, b, b) -> a -> (t a, b, b)
forall c (t :: * -> *) a.
(Ord c, Monoid (t a), InsertLeft t a, Num c) =>
(t a, c, c) -> a -> (t a, c, c)
f (t a, b, b)
v
 where v :: (t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: (t a, c, c) -> a -> (t a, c, c)
f (t a
zs,c
k,c
n) a
x
        | c
k c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
n = (t a
zs t a -> t a -> t a
forall a. Monoid a => a -> a -> a
`mappend` (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
forall a. Monoid a => a
mempty),c
k c -> c -> c
forall a. Num a => a -> a -> a
+ c
1,c
n)
        | Bool
otherwise = (t a
zs,c
k,c
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.
reverseDropG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a
reverseDropG :: b -> t a -> t a
reverseDropG b
n = (\(t a
xs,b
_,b
_) -> t a
xs) ((t a, b, b) -> t a) -> (t a -> (t a, b, b)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((t a, b, b) -> a -> (t a, b, b))
-> (t a, b, b) -> t a -> (t a, b, b)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' (t a, b, b) -> a -> (t a, b, b)
forall c (t :: * -> *) a.
(Ord c, Monoid (t a), Num c, InsertLeft t a) =>
(t a, c, c) -> a -> (t a, c, c)
f (t a, b, b)
v
 where v :: (t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: (t a, c, c) -> a -> (t a, c, c)
f (t a
zs,c
k,c
n) a
x
        | c
k c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
n = (t a
forall a. Monoid a => a
mempty,c
k c -> c -> c
forall a. Num a => a -> a -> a
+ c
1,c
n)
        | Bool
otherwise = (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
zs,c
k,c
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.
dropFromEndG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a
dropFromEndG :: b -> t a -> t a
dropFromEndG b
n = (\(t a
xs,b
_,b
_) -> t a
xs) ((t a, b, b) -> t a) -> (t a -> (t a, b, b)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (t a, b, b) -> (t a, b, b))
-> (t a, b, b) -> t a -> (t a, b, b)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> (t a, b, b) -> (t a, b, b)
forall c (t :: * -> *) a.
(Ord c, Monoid (t a), Num c, InsertLeft t a) =>
a -> (t a, c, c) -> (t a, c, c)
f (t a, b, b)
v
 where v :: (t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: a -> (t a, c, c) -> (t a, c, c)
f a
x (t a
zs,c
k,c
n)
        | c
k c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
n = (t a
forall a. Monoid a => a
mempty,c
k c -> c -> c
forall a. Num a => a -> a -> a
+ c
1,c
n)
        | Bool
otherwise = (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
zs,c
k,c
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.
reverseDropFromEndG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a
reverseDropFromEndG :: b -> t a -> t a
reverseDropFromEndG b
n = (\(t a
xs,b
_,b
_) -> t a
xs) ((t a, b, b) -> t a) -> (t a -> (t a, b, b)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (t a, b, b) -> (t a, b, b))
-> (t a, b, b) -> t a -> (t a, b, b)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> (t a, b, b) -> (t a, b, b)
forall c (t :: * -> *) a.
(Ord c, Monoid (t a), Num c, InsertLeft t a) =>
a -> (t a, c, c) -> (t a, c, c)
f (t a, b, b)
v
 where v :: (t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: a -> (t a, c, c) -> (t a, c, c)
f a
x (t a
zs,c
k,c
n)
        | c
k c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
n = (t a
forall a. Monoid a => a
mempty,c
k c -> c -> c
forall a. Num a => a -> a -> a
+ c
1,c
n)
        | Bool
otherwise = (t a
zs t a -> t a -> t a
forall a. Monoid a => a -> a -> a
`mappend` (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
forall a. Monoid a => a
mempty),c
k,c
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.
dropG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> t a
dropG :: b -> t a -> t a
dropG b
n = (\(t a
xs,b
_,b
_) -> t a
xs) ((t a, b, b) -> t a) -> (t a -> (t a, b, b)) -> t a -> t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((t a, b, b) -> a -> (t a, b, b))
-> (t a, b, b) -> t a -> (t a, b, b)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' (t a, b, b) -> a -> (t a, b, b)
forall c (t :: * -> *) a.
(Ord c, Monoid (t a), Num c, InsertLeft t a) =>
(t a, c, c) -> a -> (t a, c, c)
f (t a, b, b)
v
 where v :: (t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: (t a, c, c) -> a -> (t a, c, c)
f (t a
zs,c
k,c
n) a
x
        | c
k c -> c -> Bool
forall a. Ord a => a -> a -> Bool
< c
n = (t a
forall a. Monoid a => a
mempty,c
k c -> c -> c
forall a. Num a => a -> a -> a
+ c
1,c
n)
        | Bool
otherwise = (t a
zs t a -> t a -> t a
forall a. Monoid a => a -> a -> a
`mappend` (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
forall a. Monoid a => a
mempty),c
k,c
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.
splitAtG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> (t a, t a)
splitAtG :: b -> t a -> (t a, t a)
splitAtG b
n = (\(t a
x,t a
y,b
_,b
_) -> (t a
x,t a
y)) ((t a, t a, b, b) -> (t a, t a))
-> (t a -> (t a, t a, b, b)) -> t a -> (t a, t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((t a, t a, b, b) -> a -> (t a, t a, b, b))
-> (t a, t a, b, b) -> t a -> (t a, t a, b, b)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' (t a, t a, b, b) -> a -> (t a, t a, b, b)
forall a (t :: * -> *) a (t :: * -> *).
(Ord a, Monoid (t a), Monoid (t a), Num a, InsertLeft t a,
 InsertLeft t a) =>
(t a, t a, a, a) -> a -> (t a, t a, a, a)
f (t a, t a, b, b)
v
 where v :: (t a, t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: (t a, t a, a, a) -> a -> (t a, t a, a, a)
f (t a
zs,t a
ts,a
k,a
n) a
x
        | a
k a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
n = (t a
zs t a -> t a -> t a
forall a. Monoid a => a -> a -> a
`mappend` (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
forall a. Monoid a => a
mempty),t a
forall a. Monoid a => a
mempty,a
k a -> a -> a
forall a. Num a => a -> a -> a
+ a
1,a
n)
        | Bool
otherwise = (t a
zs,t a
ts t a -> t a -> t a
forall a. Monoid a => a -> a -> a
`mappend` (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
forall a. Monoid a => a
mempty),a
k a -> a -> a
forall a. Num a => a -> a -> a
+ a
1,a
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. Splits the structure starting from the end and preserves the order.
splitAtEndG :: (Integral b, InsertLeft t a, Monoid (t a)) => b -> t a -> (t a, t a)
splitAtEndG :: b -> t a -> (t a, t a)
splitAtEndG b
n = (\(t a
x,t a
y,b
_,b
_) -> (t a
y,t a
x)) ((t a, t a, b, b) -> (t a, t a))
-> (t a -> (t a, t a, b, b)) -> t a -> (t a, t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (t a, t a, b, b) -> (t a, t a, b, b))
-> (t a, t a, b, b) -> t a -> (t a, t a, b, b)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> (t a, t a, b, b) -> (t a, t a, b, b)
forall a (t :: * -> *) a (t :: * -> *).
(Ord a, Monoid (t a), Num a, InsertLeft t a, InsertLeft t a) =>
a -> (t a, t a, a, a) -> (t a, t a, a, a)
f (t a, t a, b, b)
v
 where v :: (t a, t a, b, b)
v = (t a
forall a. Monoid a => a
mempty,t a
forall a. Monoid a => a
mempty,b
0,b
n)
       f :: a -> (t a, t a, a, a) -> (t a, t a, a, a)
f a
x (t a
zs,t a
ts,a
k,a
n)
        | a
k a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
n = (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
zs,t a
forall a. Monoid a => a
mempty,a
k a -> a -> a
forall a. Num a => a -> a -> a
+ a
1,a
n)
        | Bool
otherwise = (t a
zs,a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
ts,a
k a -> a -> a
forall a. Num a => a -> a -> a
+ a
1,a
n)

-- | If a structure is empty, just returns 'Nothing'.
safeHeadG :: (Foldable t) => t a -> Maybe a
safeHeadG :: t a -> Maybe a
safeHeadG = (a -> Bool) -> t a -> Maybe a
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
F.find (Bool -> a -> Bool
forall a b. a -> b -> a
const Bool
True)

-- | If the structure is empty, just returns itself. Uses strict variant of the foldl, so is
-- strict and the data must be finite.
safeTailG :: (InsertLeft t a, Monoid (t a)) => t a -> t a
safeTailG :: t a -> t a
safeTailG = Integer -> t a -> t a
forall b (t :: * -> *) a.
(Integral b, InsertLeft t a, Monoid (t a)) =>
b -> t a -> t a
dropG Integer
1

-- | If the structure is empty, just returns itself.
safeInitG :: (InsertLeft t a, Monoid (t a)) => t a -> t a
safeInitG :: t a -> t a
safeInitG = Integer -> t a -> t a
forall b (t :: * -> *) a.
(Integral b, InsertLeft t a, Monoid (t a)) =>
b -> t a -> t a
dropFromEndG Integer
1

-- | If the structure is empty, just returns 'Nothing'.
safeLastG :: (InsertLeft t a, Monoid (t a)) => t a -> Maybe a
safeLastG :: t a -> Maybe a
safeLastG = (a -> Bool) -> t a -> Maybe a
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
F.find (Bool -> a -> Bool
forall a b. a -> b -> a
const Bool
True) (t a -> Maybe a) -> (t a -> t a) -> t a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> t a -> t a
forall b (t :: * -> *) a.
(Integral b, InsertLeft t a, Monoid (t a)) =>
b -> t a -> t a
takeFromEndG Integer
1

-----------------------------------------------------------------------------

-- | 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. Acts similarly to the 'map' function from Prelude.
mapG :: (InsertLeft t b, Monoid (t b)) => (a -> b) -> t a -> t b
mapG :: (a -> b) -> t a -> t b
mapG a -> b
f = (a -> t b -> t b) -> t b -> t a -> t b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr (\a
x t b
ys -> a -> b
f a
x b -> t b -> t b
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t b
ys) t b
forall a. Monoid a => a
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. Acts similarly to 'filter' function from Prelude.
filterG :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> t a
filterG :: (a -> Bool) -> t a -> t a
filterG a -> Bool
p = (a -> t a -> t a) -> t a -> t a -> t a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr (\a
x t a
ys -> if a -> Bool
p a
x then a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
ys else t a
ys) t a
forall a. Monoid a => a
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. Acts similarly to 'partition' function from Data.List. Practically is a
-- rewritten for more general variants function partition from https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.OldList.html#partition
partitionG :: (InsertLeft t a, Monoid (t a)) => (a -> Bool) -> t a -> (t a, t a)
partitionG :: (a -> Bool) -> t a -> (t a, t a)
partitionG a -> Bool
p = (a -> (t a, t a) -> (t a, t a)) -> (t a, t a) -> t a -> (t a, t a)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr (\a
x (t a
ys,t a
zs) -> if a -> Bool
p a
x then (a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
ys,t a
zs) else (t a
ys,a
x a -> t a -> t a
forall (t :: * -> *) a. InsertLeft t a => a -> t a -> t a
%@ t a
zs)) (t a
forall a. Monoid a => a
mempty,t a
forall a. Monoid a => a
mempty)