Streamly: Internal: Data: Clean up hlint warnings

Signed-off-by: Sanchayan Maity <maitysanchayan@gmail.com>
This commit is contained in:
Sanchayan Maity 2020-06-04 19:54:38 +05:30 committed by Pranay Sashank
parent 96f01fd134
commit b5cf9dd9a7
10 changed files with 36 additions and 51 deletions

View File

@ -1,6 +1,5 @@
src/Streamly/Internal/BaseCompat.hs
src/Streamly/Internal/Control/Monad.hs
src/Streamly/Internal/Data/SVar.hs
src/Streamly/Internal/Data/Stream/SVar.hs
src/Streamly/Internal/Data/Stream/Serial.hs
src/Streamly/Internal/Data/Stream/Zip.hs
@ -14,16 +13,11 @@ src/Streamly/Internal/Data/Stream/Ahead.hs
src/Streamly/Internal/Data/Stream/StreamD/Type.hs
src/Streamly/Internal/Data/Stream/StreamDK/Type.hs
src/Streamly/Internal/Data/Stream/StreamD.hs
src/Streamly/Internal/Data/SmallArray.hs
src/Streamly/Internal/Data/Pipe/Types.hs
src/Streamly/Internal/Data/Pipe.hs
src/Streamly/Internal/Data/Sink/Types.hs
src/Streamly/Internal/Data/Sink.hs
src/Streamly/Internal/Data/Zipper/Array.hs
src/Streamly/Internal/Data/Parser/ParserD/Types.hs
src/Streamly/Internal/Data/Parser/ParserD.hs
src/Streamly/Internal/Data/Time/Units.hs
src/Streamly/Internal/Data/Prim/Array.hs
src/Streamly/Internal/Data/Prim/Array/Types.hs
src/Streamly/Internal/Data/SmallArray/Types.hs
src/Streamly/Internal/Data/Unfold.hs

View File

@ -1182,8 +1182,8 @@ distribute_ fs = Fold step initial extract
step ss a = do
Prelude.mapM_ (\(Fold s i _) -> i >>= \r -> void (s r a)) ss
return ss
extract ss =
Prelude.mapM_ (\(Fold _ i e) -> i >>= \r -> e r) ss
extract =
Prelude.mapM_ (\(Fold _ i e) -> i >>= \r -> e r)
------------------------------------------------------------------------------
-- Partitioning

View File

@ -1,9 +1,7 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- |

View File

@ -158,18 +158,18 @@ zipWith f (Pipe consumeL produceL stateL) (Pipe consumeR produceR stateR) =
where
{-# INLINE drive #-}
drive st res queue fConsume fProduce val = do
drive st res queue fConsume fProduce val =
case res of
Nothing -> goConsume st queue val fConsume fProduce
Just x -> return $
case queue of
Nothing -> (st, Just x, Just $ (Deque [val] []))
Nothing -> (st, Just x, Just $ Deque [val] [])
Just q -> (st, Just x, Just $ snoc val q)
{-# INLINE goConsume #-}
goConsume stt queue val fConsume stp2 = do
goConsume stt queue val fConsume stp2 =
case stt of
Consume st -> do
Consume st ->
case queue of
Nothing -> do
r <- fConsume st val
@ -200,15 +200,15 @@ zipWith f (Pipe consumeL produceL stateL) (Pipe consumeR produceR stateR) =
where
{-# INLINE drive #-}
drive stt res q fConsume fProduce = do
drive stt res q fConsume fProduce =
case res of
Nothing -> goProduce stt q fConsume fProduce
Just x -> return (stt, Just x, q)
{-# INLINE goProduce #-}
goProduce stt queue fConsume fProduce = do
goProduce stt queue fConsume fProduce =
case stt of
Consume st -> do
Consume st ->
case queue of
-- See yieldOutput. We enter produce mode only when
-- each pipe is either in Produce state or the
@ -269,7 +269,7 @@ tee (Pipe consumeL produceL stateL) (Pipe consumeR produceR stateR) =
state = Tuple' (Consume stateL) (Consume stateR)
consume (Tuple' sL sR) a = do
consume (Tuple' sL sR) a =
case sL of
Consume st -> do
r <- consumeL st a
@ -286,9 +286,9 @@ tee (Pipe consumeL produceL stateL) (Pipe consumeR produceR stateR) =
Continue s -> Continue (Right (Tuple3' (Just a) s sR))
-}
produce (Tuple3' (Just a) sL sR) = do
produce (Tuple3' (Just a) sL sR) =
case sL of
Consume _ -> do
Consume _ ->
case sR of
Consume st -> do
r <- consumeR st a
@ -309,7 +309,7 @@ tee (Pipe consumeL produceL stateL) (Pipe consumeR produceR stateR) =
Yield x s -> Yield x (next s)
Continue s -> Continue (next s)
produce (Tuple3' Nothing sL sR) = do
produce (Tuple3' Nothing sL sR) =
case sR of
Consume _ -> undefined -- should never occur
Produce st -> do
@ -359,7 +359,7 @@ compose (Pipe consumeL produceL stateL) (Pipe consumeR produceR stateR) =
state = Tuple' (Consume stateL) (Consume stateR)
consume (Tuple' sL sR) a = do
consume (Tuple' sL sR) a =
case sL of
Consume stt ->
case sR of
@ -392,7 +392,7 @@ compose (Pipe consumeL produceL stateL) (Pipe consumeR produceR stateR) =
-- XXX we need to write the code in mor optimized fashion. Use Continue
-- more and less yield points.
produce (Tuple' sL sR) = do
produce (Tuple' sL sR) =
case sL of
Produce st -> do
r <- produceL st

View File

@ -1,8 +1,6 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
#include "inline.hs"
@ -80,7 +78,7 @@ toStreamD arr = D.Stream step 0
{-# INLINE length #-}
length :: Prim a => PrimArray a -> Int
length arr = sizeofPrimArray arr
length = sizeofPrimArray
{-# INLINE_NORMAL toStreamDRev #-}
toStreamDRev :: (Prim a, Monad m) => PrimArray a -> D.Stream m a
@ -139,14 +137,14 @@ fromStreamDN limit str = do
marr <- liftIO $ newPrimArray (max limit 0)
_ <-
D.foldlM'
(\i x -> i `seq` (liftIO $ writePrimArray marr i x) >> return (i + 1))
(\i x -> i `seq` liftIO (writePrimArray marr i x) >> return (i + 1))
0 $
D.take limit str
liftIO $ unsafeFreezePrimArray marr
{-# INLINE fromStreamD #-}
fromStreamD :: (MonadIO m, Prim a) => D.Stream m a -> m (PrimArray a)
fromStreamD str = D.runFold write str
fromStreamD = D.runFold write
{-# INLINABLE fromListN #-}
fromListN :: Prim a => Int -> [a] -> PrimArray a

View File

@ -143,7 +143,7 @@ import Data.Kind (Type)
#endif
import Data.IORef
(IORef, modifyIORef, newIORef, readIORef, writeIORef, atomicModifyIORef)
import Data.Maybe (fromJust)
import Data.Maybe (fromJust, fromMaybe)
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup ((<>))
#endif
@ -704,7 +704,7 @@ collectWorkerPendingLatency cur col = do
assert (latCount == 0 || latTime /= 0) (return ())
let latPair =
if latCount > 0 && latTime > 0
then Just $ (latCount, latTime)
then Just (latCount, latTime)
else Nothing
return (totalCount, latPair)
@ -748,7 +748,7 @@ collectLatency sv yinfo drain = do
case newLatPair of
Nothing -> retWith prevLat
Just (count, time) -> do
let newLat = time `div` (fromIntegral count)
let newLat = time `div` fromIntegral count
when (svarInspectMode sv) $ recordMinMaxLatency sv newLat
-- When we have collected a significant sized batch we compute the
-- new latency using that batch and return the new latency,
@ -1102,7 +1102,7 @@ sendWithDoorBell q bell msg = do
-- | This function is used by the producer threads to queue output for the
-- consumer thread to consume. Returns whether the queue has more space.
send :: SVar t m a -> ChildEvent a -> IO Int
send sv msg = sendWithDoorBell (outputQueue sv) (outputDoorBell sv) msg
send sv = sendWithDoorBell (outputQueue sv) (outputDoorBell sv)
-- There is no bound implemented on the buffer, this is assumed to be low
-- traffic.
@ -1856,10 +1856,7 @@ dispatchWorkerPaced sv = do
let elapsed = fromRelTime64 $ diffAbsTime64 now baseTime
let latency =
if lat == 0
then
case workerBootstrapLatency yinfo of
Nothing -> lat
Just t -> t
then fromMaybe lat (workerBootstrapLatency yinfo)
else lat
return (yieldCount, elapsed, latency)
@ -2349,7 +2346,7 @@ getParallelSVar ss st mrun = do
let bufLim =
case getMaxBuffer st of
Unlimited -> undefined
Limited x -> (fromIntegral x)
Limited x -> fromIntegral x
remBuf <- newIORef bufLim
pbMVar <- newMVar ()

View File

@ -21,4 +21,4 @@ where
-- bit more efficient than a 'Fold' with '()' as the state, especially when
-- 'Sink's are composed with other operations. A Sink can be upgraded to a
-- 'Fold', but a 'Fold' cannot be converted into a Sink.
data Sink m a = Sink (a -> m ())
newtype Sink m a = Sink (a -> m ())

View File

@ -65,7 +65,7 @@ bottomElement = undefined
{-# INLINE length #-}
length :: SmallArray a -> Int
length arr = sizeofSmallArray arr
length = sizeofSmallArray
{-# INLINE_NORMAL toStreamD #-}
toStreamD :: Monad m => SmallArray a -> D.Stream m a
@ -124,7 +124,7 @@ fromStreamDN limit str = do
marr <- liftIO $ newSmallArray (max limit 0) bottomElement
i <-
D.foldlM'
(\i x -> i `seq` (liftIO $ writeSmallArray marr i x) >> return (i + 1))
(\i x -> i `seq` liftIO (writeSmallArray marr i x) >> return (i + 1))
0 $
D.take limit str
liftIO $ freezeSmallArray marr 0 i

View File

@ -300,7 +300,7 @@ traverseSmallArrayP
=> (a -> m b)
-> SmallArray a
-> m (SmallArray b)
traverseSmallArrayP f = \ !ary ->
traverseSmallArrayP f !ary =
let
!sz = sizeofSmallArray ary
go !i !mary
@ -442,7 +442,7 @@ instance Ord1 SmallArray where
-- | Lexicographic ordering. Subject to change between major versions.
instance Ord a => Ord (SmallArray a) where
compare sa1 sa2 = smallArrayLiftCompare compare sa1 sa2
compare = smallArrayLiftCompare compare
instance Foldable SmallArray where
-- Note: we perform the array lookups eagerly so we won't
@ -757,7 +757,7 @@ listLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> Show
listLiftShowsPrec _ sl _ = sl
instance Show a => Show (SmallArray a) where
showsPrec p sa = smallArrayLiftShowsPrec showsPrec showList p sa
showsPrec = smallArrayLiftShowsPrec showsPrec showList
#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0)
-- | @since 0.6.4.0

View File

@ -168,7 +168,7 @@ instance Ord TimeSpec where
addWithOverflow :: TimeSpec -> TimeSpec -> TimeSpec
addWithOverflow (TimeSpec s1 ns1) (TimeSpec s2 ns2) =
let nsum = ns1 + ns2
(s', ns) = if (nsum > tenPower9 || nsum < negate tenPower9)
(s', ns) = if nsum > tenPower9 || nsum < negate tenPower9
then nsum `divMod` tenPower9
else (0, nsum)
in TimeSpec (s1 + s2 + s') ns
@ -176,12 +176,10 @@ addWithOverflow (TimeSpec s1 ns1) (TimeSpec s2 ns2) =
-- make sure both sec and nsec have the same sign
{-# INLINE adjustSign #-}
adjustSign :: TimeSpec -> TimeSpec
adjustSign (t@(TimeSpec s ns)) =
if (s > 0 && ns < 0)
then TimeSpec (s - 1) (ns + tenPower9)
else if (s < 0 && ns > 0)
then TimeSpec (s + 1) (ns - tenPower9)
else t
adjustSign t@(TimeSpec s ns)
| s > 0 && ns < 0 = TimeSpec (s - 1) (ns + tenPower9)
| s < 0 && ns > 0 = TimeSpec (s + 1) (ns - tenPower9)
| otherwise = t
{-# INLINE timeSpecToInteger #-}
timeSpecToInteger :: TimeSpec -> Integer
@ -193,7 +191,7 @@ instance Num TimeSpec where
-- XXX will this be more optimal if imlemented without "negate"?
{-# INLINE (-) #-}
t1 - t2 = t1 + (negate t2)
t1 - t2 = t1 + negate t2
t1 * t2 = fromInteger $ timeSpecToInteger t1 * timeSpecToInteger t2
{-# INLINE negate #-}