-- | -- Module : Data.List.InnToOut.Unsafe -- Copyright : (c) OleksandrZhabenko 2019 -- License : MIT -- -- Maintainer : olexandr543@yahoo.com -- -- Various additional operations on lists that have additional intermediate Monads inside. -- module Data.List.InnToOut.Unsafe ( -- * Operations to obtain intermediate Monads. Like the 'unsafePerformIO' function they can have unpredictable behaviour. Use them ONLY if you surely know what you are doing. unsafeMapI22M ,unsafeMapI2M2 ,unsafeMapI2M2M ,unsafeMapI12M ,unsafeMapI2M1 ) where -- | Variant of the function 'Data.List.InnToOut.Basic.mapI22' in which the second intermediate result @c@ is in the @Monad m@. unsafeMapI22M :: Monad m => (a -> Bool) -> (a -> b) -> (b -> d) -> (a -> m c) -> (m c -> d) -> [a] -> [d] unsafeMapI22M p f1 g f2 h = map (\x -> if p x then g (f1 x) else h (f2 x)) {-#INLINE unsafeMapI22M#-} -- | Variant of the function 'Data.List.InnToOut.Basic.mapI22' in which the first intermediate result @b@ is in the @Monad m@. unsafeMapI2M2 :: Monad m => (a -> Bool) -> (a -> m b) -> (m b -> d) -> (a -> c) -> (c -> d) -> [a] -> [d] unsafeMapI2M2 p f1 g f2 h = map (\x -> if p x then g (f1 x) else h (f2 x)) {-#INLINE unsafeMapI2M2#-} -- | Variant of the function 'Data.List.InnToOut.Basic.mapI22' in which both the intermediate results @b@ and @c@ are in the Monads. unsafeMapI2M2M :: (Monad m0, Monad m) => (a -> Bool) -> (a -> m0 b) -> (m0 b -> d) -> (a -> m c) -> (m c -> d) -> [a] -> [d] unsafeMapI2M2M p f1 g f2 h = map (\x -> if p x then g (f1 x) else h (f2 x)) {-#INLINE unsafeMapI2M2M#-} -- | Variant of the function 'Data.List.InnToOut.Basic.mapI12' in which the second intermediate result @b@ is in the @Monad m@. unsafeMapI12M :: Monad m => (a -> Bool) -> (a -> c) -> (a -> m b) -> (m b -> c) -> [a] -> [c] unsafeMapI12M p f g h = map (\x -> if p x then f x else h (g x)) {-#INLINE unsafeMapI12M#-} -- | Variant of the function 'Data.List.InnToOut.Basic.mapI21' in which the first intermediate result @b@ is in the @Monad m@. unsafeMapI2M1 :: Monad m => (a -> Bool) -> (a -> m b) -> (m b -> c) -> (a -> c) -> [a] -> [c] unsafeMapI2M1 p f g h = map (\x -> if p x then g (f x) else h x) {-#INLINE unsafeMapI2M1#-}