-- | Extra functions for dealing with lists. module Data.List.Extra where import Control.Arrow import Data.Bool.Extra import Data.List import Data.Maybe import Data.Ord -- | When a list is non-null, pass it to a function, otherwise use the -- default. list :: b -> ([a] -> b) -> [a] -> b list nil cons = cond (const nil) cons null -- | Get the union of the given lists. unionOf :: (Eq a) => [[a]] -> [a] unionOf = foldr union [] -- | Opposite of map. for :: [a] -> (a -> b) -> [b] for = flip map -- | Maybe get the last element in the list. lastToMaybe :: [a] -> Maybe a lastToMaybe [x] = Just x lastToMaybe (_:xs) = lastToMaybe xs lastToMaybe [] = Nothing -- | Return the first item of a list or something else. firstOr :: a -> [a] -> a firstOr n = fromMaybe n . listToMaybe -- | Get the maximum of a list or return zero. maxList :: (Num t, Ord t) => [t] -> t maxList [] = 0 maxList xs = maximum xs -- | Sort a list using a key on each element. This implements the -- decorate-sort-undecorate paradigm, also called a Schwarzian transform. sortByKey :: Ord b => (a -> b) -> [a] -> [a] sortByKey f = map snd . sortBy (comparing fst) . map (f &&& id)