-- | Prelude replacement, use the NoImplicitPrelude extension before importing this. -- -- It deliberately omits all list-handling functions, import Data.List or use the generic versions. module Prelude.Classy( -- * Basic/legacy types module Data.Bool, bool, module Data.Maybe, module Data.Either, module Data.Eq, module Data.Ord, Enum(..), Char, String(..), fst, snd, lines, words, unlines, unwords, Show(..), Read(..), read, -- * Basic I/O IO, putChar, putStr, putStrLn, print, getChar, getLine, readFile, writeFile, appendFile, readIO, readLn, -- * Basic function composition curry, uncurry, first, second, id, const, (.), flip, ($), until, -- * Integer math Int, Integer, Bounded(..), Num(..), Integral(..), subtract, even, odd, (^), fromIntegral, -- * Monad hierarchy module Control.Applicative, module Control.Monad, -- * Monoids, Foldables and other goodies module Data.Monoid, (<>), module Data.Foldable, module Data.Traversable, -- * Misc. asTypeOf, error, undefined, seq, ($!) ) where import Data.Bool import Data.Maybe import Data.Either import Data.Ord import Data.Eq import Prelude(Char,String(..),fst,snd,curry,uncurry,Bounded(..), Num(..), Integral(..), Enum(..), lines, words, unlines, unwords, Show(..), Read(..), read, IO, putChar, putStr, putStrLn, print, getChar, writeFile, appendFile, readIO, readLn, getLine, id, const, (.), flip, until, asTypeOf, error, undefined, seq, subtract, even, odd, (^), fromIntegral, Int, Integer) import Control.Arrow(first,second) import Control.Applicative import Control.Monad hiding(mapM, mapM_, sequence, sequence_, forM, forM_, msum) import Data.Monoid import Data.Foldable import Data.Traversable import System.IO.Strict(readFile) -- | An either/maybe equivalent for Bool, often known as if' bool :: a -- ^ Returned if the bool is True -> a -- ^ Returned if the bool is False -> Bool -> a bool a _ True = a bool _ a False = a infixr 5 <> -- | (<>) = mappend a <> b = mappend a b filter :: (Monad m, Monoid (m a), Foldable t) => (a -> Bool) -> t a -> m a filter p = foldMap (\a -> bool (return a) mempty (p a)) infixl 0 $, $! -- | *Left-associative* version of Prelude.$ f $ x = f x -- | *Left-associative* version of Prelude.$! f $! x = x `seq` f x