Fix hlint hints

This commit is contained in:
Harendra Kumar 2020-07-26 17:03:44 +05:30
parent cd7869d219
commit 9851d18f9d
4 changed files with 5 additions and 5 deletions

View File

@ -342,7 +342,7 @@ split_ (Parser stepL initialL extractL) (Parser stepR initialR extractR) =
-- Note: For the composed parse to terminate, the left parser has to be
-- a terminating parser returning a Done at some point.
step (SeqAL st) a = do
step (SeqAL st) a =
(\r i -> case r of
-- Note: this leads to buffering even if we are not in an
-- Alternative composition.
@ -352,7 +352,7 @@ split_ (Parser stepL initialL extractL) (Parser stepR initialR extractR) =
-- XXX should we sequence initialR monadically?
Error err -> Error err) <$> stepL st a <*> initialR
step (SeqAR st) a = do
step (SeqAR st) a =
(\case
Partial n s -> Partial n (SeqAR s)
Continue n s -> Continue n (SeqAR s)

View File

@ -231,7 +231,7 @@ parse pstep initial extract (Zipper (cp:cps) backward forward) cont =
fwd = Prelude.reverse fwd0
assert (cp + cnt1 - n >= 0) (return ())
cont (Zipper (cp + cnt1 - n : cps) [] fwd) (Done b)
D.Partial 0 pst1 -> do
D.Partial 0 pst1 ->
return $ Partial (parseCont cnt1 [] (return pst1))
D.Partial n pst1 -> do
assert (n <= length (x:back)) (return ())

View File

@ -373,7 +373,7 @@ consM action unf = Unfold step inject
inject = return . Left
{-# INLINE_LATE step #-}
step (Left a) = do
step (Left a) =
action a >>= \r -> return $ Yield r (Right (D.unfold unf a))
step (Right (UnStream step1 st)) = do
res <- step1 defState st

View File

@ -105,7 +105,7 @@ nil = Zipper [] [] []
--
{-# INLINE fromList #-}
fromList :: [a] -> Zipper a
fromList xs = Zipper [] [] xs
fromList = Zipper [] []
-------------------------------------------------------------------------------
-- Checkpointing