-- | -- Module : Sublists -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Allows to split lists into sublists with some patterns by quantity. module Sublists where {-| Splits the input second argument into sublists each one containing the @n@ elements where the number is taken as the sequential element in the first argument starting from the left to the right. If the number is less than 1 then the corresponding sublist is empty. If all the elements in the first argument are less than 1 then returns an infinite lazy list of [] as its elements (probably not the needed case). When all the elements of the first argument ends and there are elements in the second argument being not already processed then the function reinitializes itself with the prior first argument and the rest of the unprocessed elements in the second argument. This leads to the *cycling behaviour*. If the first argument is less than 1 then returns an infinite lazy list of the [] as its elements (probably not the needed case). Similar functions are in the @list-grouping@ and @split@ packages, but they do not have cycling behaviour and have another realization. -} intoRegularSublists :: [Int] -> [a] -> [[a]] intoRegularSublists (n:ns) xs | null xs = [] | otherwise = ts : intoRegularSublists' ns zs (n:ns) where (ts, zs) = splitAt n xs intoRegularSublists' (r:rs) ys us | null ys = [] | otherwise = ws : intoRegularSublists' rs vs us where (ws,vs) = splitAt r ys intoRegularSublists' _ ys us = intoRegularSublists' us ys us intoRegularSublists _ xs = [xs] {-# INLINABLE intoRegularSublists #-} {-| A monadic variant of the 'intoRegularSublists' where the first argument is taken from the monadic function. -} intoRegularSublistsM :: (Monad m) => (a -> m [Int]) -- ^ A monadic function to obtain the argument for the regularization. -> a -- ^ An initial element (seed) for the monadic function. -> [b] -- ^ A list to be splitted into the sublists. -> m [[b]] intoRegularSublistsM f seed xs | null xs = return [] | otherwise = f seed >>= \ns -> return . intoRegularSublists ns $ xs {-# INLINABLE intoRegularSublistsM #-}