Optimize "foldl"

This commit is contained in:
Nikita Volkov 2015-11-21 12:01:32 +03:00
parent 103c80090a
commit 89470ff672
2 changed files with 7 additions and 1 deletions

View File

@ -182,7 +182,7 @@ foldl step init rowDes =
maxCols <- LibPQ.nfields result maxCols <- LibPQ.nfields result
accRef <- newIORef init accRef <- newIORef init
failureRef <- newIORef Nothing failureRef <- newIORef Nothing
forM_ [0 .. pred (rowToInt maxRows)] $ \rowIndex -> do forMFromZero_ (rowToInt maxRows) $ \rowIndex -> do
rowResult <- Row.run rowDes (result, intToRow rowIndex, maxCols, integerDatetimes) rowResult <- Row.run rowDes (result, intToRow rowIndex, maxCols, integerDatetimes)
case rowResult of case rowResult of
Left x -> writeIORef failureRef (Just (RowError rowIndex x)) Left x -> writeIORef failureRef (Just (RowError rowIndex x))

View File

@ -8,6 +8,7 @@ module Hasql.Prelude
bug, bug,
bottom, bottom,
forMToZero_, forMToZero_,
forMFromZero_,
strictCons, strictCons,
) )
where where
@ -122,6 +123,11 @@ forMToZero_ :: Applicative m => Int -> (Int -> m a) -> m ()
forMToZero_ !startN f = forMToZero_ !startN f =
($ pred startN) $ fix $ \loop !n -> if n >= 0 then f n *> loop (pred n) else pure () ($ pred startN) $ fix $ \loop !n -> if n >= 0 then f n *> loop (pred n) else pure ()
{-# INLINE forMFromZero_ #-}
forMFromZero_ :: Applicative m => Int -> (Int -> m a) -> m ()
forMFromZero_ !endN f =
($ 0) $ fix $ \loop !n -> if n < endN then f n *> loop (succ n) else pure ()
{-# INLINE strictCons #-} {-# INLINE strictCons #-}
strictCons :: a -> [a] -> [a] strictCons :: a -> [a] -> [a]
strictCons !a b = strictCons !a b =