-- | -- Module : Data.List.InnToOut.Basic -- Copyright : (c) OleksandrZhabenko 2019 -- License : MIT -- -- Maintainer : olexandr543@yahoo.com -- -- Various additional operations on lists -- module Data.List.InnToOut.Basic ( -- * Operations to apply a function or different functions (some can create an inner list) to an element of the outer list mapI , mapI2 , mapI22 , mapI12 , mapI21 ) where -- | Function that applies additional function @f :: a -> [a]@ to @a@ if @p a = True@ mapI :: (a -> Bool) -> (a -> [a]) -> [a] -> [a] mapI p f = concatMap (\x -> if p x then f x else [x]) {-#INLINE mapI#-} -- | Function that applies additional function @f :: a -> b@ to @a@ if @p a = True@ and otherwise another function @g :: a -> [b]@ to @[a]@ to obtain @[b]@ mapI2 :: (a -> Bool) -> (a -> b) -> (a -> [b]) -> [a] -> [b] mapI2 p f g = concatMap (\x -> if p x then [f x] else g x) {-#INLINE mapI2#-} -- | Function that can apply two different ways of computing something depending of the predicate value @p :: a -> Bool@ and the structure of transition the data for the @[a]@. -- It is used if there are two ways to transform data both of them consists of two applied functoins. Similar to arrow techniques. mapI22 :: (a -> Bool) -> (a -> b) -> (b -> d) -> (a -> c) -> (c -> d) -> [a] -> [d] mapI22 p f1 g f2 h = map (\x -> if p x then g (f1 x) else h (f2 x)) {-#INLINE mapI22#-} -- | Function that can apply two different ways of computing something depending of the predicate value @p :: a -> Bool@ and the structure of transition the data for the @[a]@. -- It is used if there are two ways to transform data and the first one consists of one function and another -- from two applied consequently ones. Similar to arrow techniques. mapI12 :: (a -> Bool) -> (a -> c) -> (a -> b) -> (b -> c) -> [a] -> [c] mapI12 p f g h = map (\x -> if p x then f x else h (g x)) {-#INLINE mapI12#-} -- | Function that can apply two different ways of computing something depending of the predicate value @p :: a -> Bool@ and the structure of transition the data for the @[a]@. -- It is used if there are two ways to transform data and the first one consists of two applied consequently functions and the second -- from one applied function. Similar to arrow techniques. mapI21 :: (a -> Bool) -> (a -> b) -> (b -> c) -> (a -> c) -> [a] -> [c] mapI21 p f g h = map (\x -> if p x then g (f x) else h x) {-#INLINE mapI21#-}