{-# LANGUAGE BangPatterns #-}
module Haskus.Utils.Flow
( MonadIO (..)
, MonadInIO (..)
, (>.>)
, (<.<)
, (|>)
, (<|)
, (||>)
, (<||)
, (|||>)
, (<|||)
, when
, unless
, whenM
, unlessM
, ifM
, guard
, void
, forever
, foldM
, foldM_
, forM
, forM_
, forMaybeM
, mapM
, mapM_
, sequence
, replicateM
, replicateM_
, filterM
, join
, (<=<)
, (>=>)
, loopM
, whileM
, intersperseM_
, forLoopM_
, forLoop
, module Haskus.Utils.Variant.Excepts
, lift
)
where
import Haskus.Utils.Variant
import Haskus.Utils.Variant.Excepts
import Haskus.Utils.Monad
import Haskus.Utils.Maybe
import Control.Monad.Trans.Class (lift)
(>.>) :: (a -> b) -> (b -> c) -> a -> c
f >.> g = \x -> g (f x)
infixl 9 >.>
(<.<) :: (b -> c) -> (a -> b) -> a -> c
f <.< g = \x -> f (g x)
infixr 9 <.<
(|>) :: a -> (a -> b) -> b
{-# INLINABLE (|>) #-}
x |> f = f x
infixl 0 |>
(<|) :: (a -> b) -> a -> b
{-# INLINABLE (<|) #-}
f <| x = f x
infixr 0 <|
(||>) :: Functor f => f a -> (a -> b) -> f b
{-# INLINABLE (||>) #-}
x ||> f = fmap f x
infixl 0 ||>
(<||) :: Functor f => (a -> b) -> f a -> f b
{-# INLINABLE (<||) #-}
f <|| x = fmap f x
infixr 0 <||
(|||>) :: (Functor f, Functor g) => f (g a) -> (a -> b) -> f (g b)
{-# INLINABLE (|||>) #-}
x |||> f = fmap (fmap f) x
infixl 0 |||>
(<|||) :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
{-# INLINABLE (<|||) #-}
f <||| x = fmap (fmap f) x
infixr 0 <|||
forMaybeM :: Monad m => [a] -> (a -> m (Maybe b)) -> m [b]
forMaybeM xs f = catMaybes <|| forM xs f
intersperseM_ :: Monad m => m () -> [a] -> (a -> m ()) -> m ()
intersperseM_ f as g = go as
where
go [] = pure ()
go [x] = g x
go (x:xs) = g x >> f >> go xs
forLoopM_ :: (Monad m) => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m ()
{-# INLINABLE forLoopM_ #-}
forLoopM_ start cond inc f = go start
where
go !x | cond x = f x >> go (inc x)
| otherwise = return ()
forLoop :: a -> (a -> Bool) -> (a -> a) -> acc -> (acc -> a -> acc) -> acc
{-# INLINABLE forLoop #-}
forLoop start cond inc acc0 f = go acc0 start
where
go acc !x
| cond x = let acc' = f acc x
in acc' `seq` go acc' (inc x)
| otherwise = acc