{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE Unsafe #-} -- | Reexports from @GHC.*@ modules of -- package. module Universum.Base ( -- * Base types module Data.Bits , module Data.Char , module Data.Int , module Data.Word -- * Base type classes , module Data.Eq , module Data.Foldable , module Data.Ord , module Data.Traversable -- * System IO , module System.IO -- * Base GHC types #if ( __GLASGOW_HASKELL__ >= 710 ) , module Data.Proxy , module Data.Typeable , module Data.Void #endif , module GHC.Base , module GHC.Enum , module GHC.Exts , module GHC.Float , module GHC.Generics , module GHC.Num , module GHC.Real , module GHC.Show #if MIN_VERSION_base(4,10,0) , module GHC.TypeNats #else , module GHC.TypeLits #endif , module GHC.Types #if ( __GLASGOW_HASKELL__ >= 800 ) , module GHC.OverloadedLabels , module GHC.ExecutionStack , module GHC.Stack #endif , ($!) ) where -- Base types import Data.Bits (xor) import Data.Char (chr) import Data.Int (Int, Int16, Int32, Int64, Int8) import Data.Word (Word, Word16, Word32, Word64, Word8, byteSwap16, byteSwap32, byteSwap64) -- IO import System.IO (FilePath, Handle, IOMode (..), stderr, stdin, stdout, withFile) -- Base typeclasses import Data.Eq (Eq (..)) import Data.Foldable (Foldable, concat, concatMap, foldlM, foldrM, maximumBy, minimumBy) import Data.Ord (Down (..), Ord (..), Ordering (..), comparing) import Data.Traversable (Traversable (..), fmapDefault, foldMapDefault, forM, mapAccumL, mapAccumR) -- Base GHC types #if ( __GLASGOW_HASKELL__ >= 710 ) import Data.Proxy (Proxy (..)) import Data.Typeable (Typeable) import Data.Void (Void, absurd, vacuous) #endif import GHC.Base (String, asTypeOf, maxInt, minInt, ord, seq, (++)) import GHC.Enum (Bounded (..), Enum (..), boundedEnumFrom, boundedEnumFromThen) import GHC.Exts (Constraint, FunPtr, Ptr) import GHC.Float (Double (..), Float (..), Floating (..)) import GHC.Generics (Generic) import GHC.Num (Integer, Num (..), subtract) import GHC.Real hiding (showSigned, (%)) import GHC.Show (Show) #if MIN_VERSION_base(4,10,0) import GHC.TypeNats (CmpNat, KnownNat, Nat, SomeNat (..), natVal, someNatVal) #else import GHC.TypeLits (CmpNat, KnownNat, Nat, SomeNat (..), natVal, someNatVal) #endif import GHC.Types (Bool, Char, Coercible, IO, Int, Ordering, Word) #if ( __GLASGOW_HASKELL__ >= 800 ) import GHC.ExecutionStack (getStackTrace, showStackTrace) import GHC.OverloadedLabels (IsLabel (..)) import GHC.Stack (CallStack, HasCallStack, callStack, currentCallStack, getCallStack, prettyCallStack, prettySrcLoc, withFrozenCallStack) #endif -- Pending GHC 8.2 we'll expose these. {- import GHC.Records as X ( HasField(..) ) <<<<<<< HEAD ======= import Data.Kind as X ( type (*) , type Type ) -} -- | Stricter version of 'Data.Function.$' operator. -- Default Prelude defines this at the toplevel module, so we do as well. -- -- >>> const 3 $ undefined -- 3 -- >>> const 3 $! undefined -- CallStack (from HasCallStack): -- error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err ($!) :: (a -> b) -> a -> b f $! x = let !vx = x in f vx infixr 0 $!