{-# LANGUAGE CPP #-}
{-# OPTIONS_HADDOCK not-home #-}
{-# OPTIONS_GHC -O2 #-}
{-# OPTIONS_GHC -Wno-x-partial #-}
module GHC.Prelude.Basic
( module X
, Applicative (..)
, module Bits
, bit
, shiftL, shiftR
, setBit, clearBit
, head, tail, init, last, unzip
, strictGenericLength
) where
import qualified Prelude
import Prelude as X hiding ((<>), Applicative(..), Foldable(..), head, tail, init, last, unzip)
import Control.Applicative (Applicative(..))
import Data.Foldable as X (Foldable (elem, foldMap, foldl, foldl', foldr, length, null, product, sum))
import Data.Foldable1 as X hiding (head, last)
import qualified Data.List as List
import qualified GHC.Data.List.NonEmpty as NE
import GHC.Stack.Types (HasCallStack)
import GHC.Bits as Bits hiding (bit, shiftL, shiftR, setBit, clearBit)
# if defined(DEBUG)
import qualified GHC.Bits as Bits (shiftL, shiftR)
# endif
{-# INLINE shiftL #-}
{-# INLINE shiftR #-}
shiftL, shiftR :: Bits.Bits a => a -> Int -> a
#if defined(DEBUG)
shiftL = Bits.shiftL
shiftR = Bits.shiftR
#else
shiftL :: forall a. Bits a => a -> Int -> a
shiftL = a -> Int -> a
forall a. Bits a => a -> Int -> a
Bits.unsafeShiftL
shiftR :: forall a. Bits a => a -> Int -> a
shiftR = a -> Int -> a
forall a. Bits a => a -> Int -> a
Bits.unsafeShiftR
#endif
{-# INLINE bit #-}
bit :: (Num a, Bits.Bits a) => Int -> a
bit :: forall a. (Num a, Bits a) => Int -> a
bit = \ Int
i -> a
1 a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
i
{-# INLINE setBit #-}
setBit :: (Num a, Bits.Bits a) => a -> Int -> a
setBit :: forall a. (Num a, Bits a) => a -> Int -> a
setBit = \ a
x Int
i -> a
x a -> a -> a
forall a. Bits a => a -> a -> a
Bits..|. Int -> a
forall a. (Num a, Bits a) => Int -> a
bit Int
i
{-# INLINE clearBit #-}
clearBit :: (Num a, Bits.Bits a) => a -> Int -> a
clearBit :: forall a. (Num a, Bits a) => a -> Int -> a
clearBit = \ a
x Int
i -> a
x a -> a -> a
forall a. Bits a => a -> a -> a
Bits..&. a -> a
forall a. Bits a => a -> a
Bits.complement (Int -> a
forall a. (Num a, Bits a) => Int -> a
bit Int
i)
head :: HasCallStack => [a] -> a
head :: forall a. HasCallStack => [a] -> a
head = [a] -> a
forall a. HasCallStack => [a] -> a
Prelude.head
{-# INLINE head #-}
tail :: HasCallStack => [a] -> [a]
tail :: forall a. HasCallStack => [a] -> [a]
tail = [a] -> [a]
forall a. HasCallStack => [a] -> [a]
Prelude.tail
{-# INLINE tail #-}
init :: HasCallStack => [a] -> [a]
init :: forall a. HasCallStack => [a] -> [a]
init = [a] -> [a]
forall a. HasCallStack => [a] -> [a]
Prelude.init
{-# INLINE init #-}
last :: HasCallStack => [a] -> a
last :: forall a. HasCallStack => [a] -> a
last = [a] -> a
forall a. HasCallStack => [a] -> a
Prelude.last
{-# INLINE last #-}
strictGenericLength :: Num a => [x] -> a
strictGenericLength :: forall a x. Num a => [x] -> a
strictGenericLength = Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> a) -> ([x] -> Int) -> [x] -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [x] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length
unzip :: Functor f => f (a, b) -> (f a, f b)
unzip :: forall (f :: * -> *) a b. Functor f => f (a, b) -> (f a, f b)
unzip = \ f (a, b)
xs -> (((a, b) -> a) -> f (a, b) -> f a
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, b) -> a
forall a b. (a, b) -> a
fst f (a, b)
xs, ((a, b) -> b) -> f (a, b) -> f b
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, b) -> b
forall a b. (a, b) -> b
snd f (a, b)
xs)
{-# NOINLINE [1] unzip #-}
{-# RULES "unzip/List" unzip = List.unzip #-}
{-# RULES "unzip/NonEmpty" unzip = NE.unzip #-}