Skip to content

Commit

Permalink
[#36] Strict append (#51)
Browse files Browse the repository at this point in the history
Resolves #36
  • Loading branch information
vrom911 authored Mar 18, 2021
1 parent a57ace2 commit bfde7cd
Show file tree
Hide file tree
Showing 2 changed files with 51 additions and 1 deletion.
2 changes: 2 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ The changelog is available [on GitHub][2].

* [#45](https://github.com/kowainik/slist/issues/45):
Support GHC-9.0. Update older GHC's bounds.
* [#36](https://github.com/kowainik/slist/issues/36):
Add strict functions: `append'`, `concat'` and `concatMap'`.
* [#30](https://github.com/kowainik/slist/issues/30):
Add the `cons` function.
* [#34](https://github.com/kowainik/slist/issues/34):
Expand Down
50 changes: 49 additions & 1 deletion src/Slist.hs
Original file line number Diff line number Diff line change
Expand Up @@ -103,6 +103,7 @@ module Slist
, safeLast
, init
, tail
, append'
, cons
, cons'
, uncons
Expand All @@ -119,7 +120,9 @@ module Slist

-- * Reducing slists (folds)
, concat
, concat'
, concatMap
, concatMap'

-- * Building slists
-- ** Scans
Expand Down Expand Up @@ -224,6 +227,7 @@ module Slist

import Data.Bifunctor (bimap, first, second)
import Data.Either (partitionEithers)
import Data.Foldable (foldl')
#if ( __GLASGOW_HASKELL__ == 802 )
import Data.Semigroup (Semigroup (..))
#endif
Expand Down Expand Up @@ -462,6 +466,18 @@ init sl@Slist{..} = case sSize of
_ -> Slist (P.init sList) (sSize - 1)
{-# INLINE init #-}

{- | Strict version of the 'Slist' appending operator '<>'.
@since x.x.x.x
-}
append' :: Slist a -> Slist a -> Slist a
append' sl1 sl2
| sSize sl1 == 0 = sl2
| sSize sl2 == 0 = sl1
| otherwise = let !newSize = sSize sl1 + sSize sl2 in Slist
{ sList = sList sl1 <> sList sl2
, sSize = newSize
}

{- | @O(1)@. Strict version of the 'cons' function
(in terms of the size evaluation).
Expand Down Expand Up @@ -659,14 +675,32 @@ permutations (Slist l s) = Slist
Slist {sList = [1,2,3,4,5,6,7,8,9,10], sSize = Size 10}
@
>> __ concat $ slist [slist [1,2], 'infiniteSlist' [3..]]__
>> __concat $ slist [slist [1,2], 'infiniteSlist' [3..]]__
Slist {sList = [1..], sSize = 'Infinity'}
@
-}
concat :: Foldable t => t (Slist a) -> Slist a
concat = foldr (<>) mempty
{-# INLINE concat #-}

{- | \( O(\sum n_i) \) The concatenation of all the elements of a container of slists.
The strict version of 'concat'.
>>> concat' [slist [1,2], slist [3..5], slist [6..10]]
Slist {sList = [1,2,3,4,5,6,7,8,9,10], sSize = Size 10}
@
>> __concat' $ slist [slist [1,2], 'infiniteSlist' [3..]]__
Slist {sList = [1..], sSize = 'Infinity'}
@
@since x.x.x.x
-}
concat' :: Foldable t => t (Slist a) -> Slist a
concat' = foldl' append' mempty
{-# INLINE concat' #-}

{- | Maps a function over all the elements of a container
and concatenates the resulting slists.
Expand All @@ -677,6 +711,20 @@ concatMap :: Foldable t => (a -> Slist b) -> t a -> Slist b
concatMap = foldMap
{-# INLINE concatMap #-}

{- | Maps a function over all the elements of a container and concatenates the
resulting slists.
Strict version of 'concatMap'.
>>> concatMap' one "abc"
Slist {sList = "abc", sSize = Size 3}
@since x.x.x.x
-}
concatMap' :: Foldable t => (a -> Slist b) -> t a -> Slist b
concatMap' f = foldl' (\acc x -> acc `append'` f x) mempty
{-# INLINE concatMap' #-}

----------------------------------------------------------------------------
-- Building lists
----------------------------------------------------------------------------
Expand Down

0 comments on commit bfde7cd

Please sign in to comment.