module Data.StorableVector.Utility where import qualified Data.List as List {-# INLINE viewListL #-} viewListL :: [a] -> Maybe (a, [a]) viewListL [] = Nothing viewListL (x:xs) = Just (x,xs) -- for constant padding {-# INLINE viewListR #-} viewListR :: [a] -> Maybe ([a], a) viewListR = List.foldr (\x -> Just . maybe ([],x) (mapFst (x:))) Nothing {-# INLINE nest #-} nest :: Int -> (a -> a) -> a -> a nest 0 _ x = x nest n f x = f (nest (n-1) f x) -- see event-list package -- | Control.Arrow.*** {-# INLINE mapPair #-} mapPair :: (a -> c, b -> d) -> (a,b) -> (c,d) mapPair ~(f,g) ~(x,y) = (f x, g y) -- | Control.Arrow.first {-# INLINE mapFst #-} mapFst :: (a -> c) -> (a,b) -> (c,b) mapFst f ~(x,y) = (f x, y) -- | Control.Arrow.second {-# INLINE mapSnd #-} mapSnd :: (b -> d) -> (a,b) -> (a,d) mapSnd g ~(x,y) = (x, g y) {-# INLINE toMaybe #-} toMaybe :: Bool -> a -> Maybe a toMaybe False _ = Nothing toMaybe True x = Just x {-# INLINE swap #-} swap :: (a,b) -> (b,a) swap (a,b) = (b,a)