Skip to content

Commit

Permalink
fixed initTails for [a]
Browse files Browse the repository at this point in the history
  • Loading branch information
BebeSparkelSparkel committed Feb 25, 2024
1 parent 3626398 commit baccd02
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 5 deletions.
8 changes: 4 additions & 4 deletions mono-traversable/src/Data/Sequences.hs
Original file line number Diff line number Diff line change
Expand Up @@ -474,13 +474,13 @@ class (Monoid seq, MonoTraversable seq, SemiSequence seq, MonoPointed seq) => Is

-- | Returns all the final segments of 'seq' with the longest first.
--
-- @since 1.0.15.4
-- @since ????
tails :: seq -> [seq]
tails x = x : maybe mempty tails (tailMay x)

-- | Return all the initial segments of 'seq' with the shortest first.
--
-- @since 1.0.15.4
-- @since ????
inits :: seq -> [seq]
inits seq = is seq [seq]
where
Expand All @@ -493,7 +493,7 @@ class (Monoid seq, MonoTraversable seq, SemiSequence seq, MonoPointed seq) => Is
-- [([],[1,2]), ([1],[2]), ([1,2],[])]
-- @
--
-- @since 1.0.15.4
-- @since ????
initTails :: seq -> [(seq,seq)]
initTails seq = List.zip (inits seq) (tails seq)

Expand Down Expand Up @@ -641,7 +641,7 @@ instance IsSequence [a] where
where
its :: ([a] -> [a]) -> [a] -> [([a],[a])]
its f xs@(y:ys) = (f [], xs) : its (f . (y:)) ys
its _ [] = []
its f [] = [(f [], [])]
{-# INLINE fromList #-}
{-# INLINE break #-}
{-# INLINE span #-}
Expand Down
24 changes: 23 additions & 1 deletion mono-traversable/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -205,9 +205,31 @@ main = hspec $ do
test "works on strict texts" T.empty
test "works on lazy texts" TL.empty

describe "inits" $ do
let test typ emptyTyp = describe typ $ do
it "empty" $ inits emptyTyp @?= [""]
it "one element" $ inits ("a" <> emptyTyp) @?= ["", "a"]
it "two elements" $ inits ("ab" <> emptyTyp) @?= ["", "a", "ab"]
test "StrictBytestring" S.empty
test "LazyBytestring" L.empty
test "StrictText" T.empty
test "LazyText" TL.empty
test "String" (mempty :: String)

describe "tails" $ do
let test typ emptyTyp = describe typ $ do
it "empty" $ tails emptyTyp @?= [""]
it "one element" $ tails ("a" <> emptyTyp) @?= ["a", ""]
it "two elements" $ tails ("ab" <> emptyTyp) @?= ["ab", "b", ""]
test "StrictBytestring" S.empty
test "LazyBytestring" L.empty
test "StrictText" T.empty
test "LazyText" TL.empty
test "String" (mempty :: String)

describe "initTails" $ do
let test typ emptyTyp = describe typ $ do
it "empty" $ initTails emptyTyp @?= []
it "empty" $ initTails emptyTyp @?= [("","")]
it "one element" $ initTails ("a" <> emptyTyp) @?= [("","a"), ("a","")]
it "two elements" $ initTails ("ab" <> emptyTyp) @?= [("","ab"), ("a","b"), ("ab","")]
test "StrictBytestring" S.empty
Expand Down

0 comments on commit baccd02

Please sign in to comment.