module Language.Haskell.HGrep.Prelude (
Bool (..)
, bool
, (&&)
, (||)
, not
, otherwise
, Char
, Integer
, Int
, Int8
, Int16
, Int32
, Int64
, Word64
, fromIntegral
, fromRational
, Monoid (..)
, (<>)
, Functor (..)
, (<$>)
, ($>)
, void
, with
, Bifunctor (..)
, Applicative (..)
, (<**>)
, Alternative (..)
, asum
, Monad (..)
, join
, MonadPlus (..)
, guard
, msum
, MonadIO (..)
, Either (..)
, either
, note
, Maybe (..)
, fromMaybe
, maybe
, hush
, fst
, snd
, curry
, uncurry
, Enum (..)
, Eq (..)
, Read (..)
, readEither
, readMaybe
, Show (..)
, ShowS
, showString
, Foldable (..)
, for_
, Ord (..)
, Ordering (..)
, comparing
, Traversable (..)
, for
, traverse_
, id
, (.)
, ($)
, ($!)
, (&)
, const
, flip
, fix
, on
, seq
, IO
, FilePath
, undefined
, error
, trace
, traceM
, traceIO
) where
import Control.Monad as Monad (
Monad (..)
, MonadPlus (..)
, guard
, join
, msum
)
import Control.Monad.IO.Class (
MonadIO (..)
)
import Control.Applicative as Applicative (
Applicative (..)
, (<**>)
, Alternative (..)
, empty
)
import Data.Bifunctor as Bifunctor (
Bifunctor (..)
)
import Data.Bool as Bool (
Bool (..)
, bool
, (&&)
, (||)
, not
, otherwise
)
import Data.Char as Char (
Char
)
import Data.Either as Either (
Either (..)
, either
)
import Data.Foldable as Foldable (
Foldable (..)
, asum
, traverse_
, for_
)
import Data.Function as Function (
id
, (.)
, ($)
, (&)
, const
, flip
, fix
, on
)
import Data.Functor as Functor (
Functor (..)
, (<$>)
, ($>)
, void
)
import Data.Eq as Eq (
Eq (..)
)
import Data.Int as Int (
Int
, Int8
, Int16
, Int32
, Int64
)
import Data.Maybe as Maybe (
Maybe (..)
, fromMaybe
, maybe
)
import Data.Monoid as Monoid (
Monoid (..)
, (<>)
)
import Data.Ord as Ord (
Ord (..)
, Ordering (..)
, comparing
)
import Data.Traversable as Traversable (
Traversable (..)
, for
)
import Data.Tuple as Tuple (
fst
, snd
, curry
, uncurry
)
import Data.Word as Word (
Word64
)
import qualified Debug.Trace as Trace
import GHC.Real as Real (
fromIntegral
, fromRational
)
#if MIN_VERSION_base(4,9,0)
import GHC.Stack (HasCallStack)
#endif
import Prelude as Prelude (
Enum (..)
, Integer
, seq
, ($!)
)
import qualified Prelude as Unsafe
import System.IO as IO (
FilePath
, IO
)
import Text.Read as Read (
Read (..)
, readEither
, readMaybe
)
import Text.Show as Show (
Show (..)
, ShowS
, showString
)
#if MIN_VERSION_base(4,9,0)
undefined :: HasCallStack => a
#else
undefined :: a
#endif
undefined =
Unsafe.undefined
#if MIN_VERSION_base(4,9,0)
error :: HasCallStack => [Char] -> a
#else
error :: [Char] -> a
#endif
error =
Unsafe.error
trace :: [Char] -> a -> a
trace =
Trace.trace
#if MIN_VERSION_base(4,9,0)
traceM :: Applicative f => [Char] -> f ()
#else
traceM :: Monad m => [Char] -> m ()
#endif
traceM =
Trace.traceM
traceIO :: [Char] -> IO ()
traceIO =
Trace.traceIO
with :: Functor f => f a -> (a -> b) -> f b
with =
flip fmap
note :: a -> Maybe b -> Either a b
note a Nothing = Left a
note _ (Just b) = Right b
hush :: Either a b -> Maybe b
hush (Left _) = Nothing
hush (Right b) = Just b