{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE DeriveDataTypeable #-}
module GHC.Exts
       (
        
        Int(..),Word(..),Float(..),Double(..),
        Char(..),
        Ptr(..), FunPtr(..),
        
        maxTupleSize,
        
        FUN, 
        module GHC.Prim,
        module GHC.Prim.Ext,
        shiftL#, shiftRL#, iShiftL#, iShiftRA#, iShiftRL#,
        isTrue#,
        Void#,  
        
        atomicModifyMutVar#,
        
        
        
        
        
        
        resizeSmallMutableArray#,
        
        build, augment,
        
        IsString(..),
        
        unpackCString#,
        unpackAppendCString#,
        unpackFoldrCString#,
        unpackCStringUtf8#,
        unpackNBytes#,
        cstringLength#,
        
        breakpoint, breakpointCond,
        
        inline, noinline, lazy, oneShot, considerAccessible, SPEC (..),
        
        runRW#,
        
        
        
        
        
        Data.Coerce.coerce, Data.Coerce.Coercible,
        
        unsafeCoerce#,
        
        type (~~),
        
        GHC.Prim.TYPE, RuntimeRep(..), Levity(..),
        LiftedRep, UnliftedRep, UnliftedType,
        VecCount(..), VecElem(..),
        
        Down(..), groupWith, sortWith, the,
        
        traceEvent,
        
        SpecConstrAnnotation(..),
        
        currentCallStack,
        
        Constraint,
        
        Any,
        
        IsList(..)
       ) where
import GHC.Prim hiding ( coerce, TYPE )
import qualified GHC.Prim
import qualified GHC.Prim.Ext
import GHC.Base hiding ( coerce )
import GHC.Ptr
import GHC.Stack
import qualified Data.Coerce
import Data.String
import Data.OldList
import Data.Data
import Data.Ord
import Data.Version ( Version(..), makeVersion )
import qualified Debug.Trace
import Unsafe.Coerce ( unsafeCoerce# ) 
import Control.Applicative (ZipList(..))
maxTupleSize :: Int
maxTupleSize :: Int
maxTupleSize = Int
64
the :: Eq a => [a] -> a
the :: forall a. Eq a => [a] -> a
the (a
x:[a]
xs)
  | forall a. (a -> Bool) -> [a] -> Bool
all (a
x forall a. Eq a => a -> a -> Bool
==) [a]
xs = a
x
  | Bool
otherwise     = forall a. [Char] -> a
errorWithoutStackTrace [Char]
"GHC.Exts.the: non-identical elements"
the []            = forall a. [Char] -> a
errorWithoutStackTrace [Char]
"GHC.Exts.the: empty list"
sortWith :: Ord b => (a -> b) -> [a] -> [a]
sortWith :: forall b a. Ord b => (a -> b) -> [a] -> [a]
sortWith a -> b
f = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (\a
x a
y -> forall a. Ord a => a -> a -> Ordering
compare (a -> b
f a
x) (a -> b
f a
y))
{-# INLINE groupWith #-}
groupWith :: Ord b => (a -> b) -> [a] -> [[a]]
groupWith :: forall b a. Ord b => (a -> b) -> [a] -> [[a]]
groupWith a -> b
f [a]
xs = forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build (\[a] -> b -> b
c b
n -> forall a lst.
([a] -> lst -> lst) -> lst -> (a -> a -> Bool) -> [a] -> lst
groupByFB [a] -> b -> b
c b
n (\a
x a
y -> a -> b
f a
x forall a. Eq a => a -> a -> Bool
== a -> b
f a
y) (forall b a. Ord b => (a -> b) -> [a] -> [a]
sortWith a -> b
f [a]
xs))
{-# INLINE [0] groupByFB #-} 
groupByFB :: ([a] -> lst -> lst) -> lst -> (a -> a -> Bool) -> [a] -> lst
groupByFB :: forall a lst.
([a] -> lst -> lst) -> lst -> (a -> a -> Bool) -> [a] -> lst
groupByFB [a] -> lst -> lst
c lst
n a -> a -> Bool
eq [a]
xs0 = [a] -> lst
groupByFBCore [a]
xs0
  where groupByFBCore :: [a] -> lst
groupByFBCore [] = lst
n
        groupByFBCore (a
x:[a]
xs) = [a] -> lst -> lst
c (a
xforall a. a -> [a] -> [a]
:[a]
ys) ([a] -> lst
groupByFBCore [a]
zs)
            where ([a]
ys, [a]
zs) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (a -> a -> Bool
eq a
x) [a]
xs
traceEvent :: String -> IO ()
traceEvent :: [Char] -> IO ()
traceEvent = [Char] -> IO ()
Debug.Trace.traceEventIO
{-# DEPRECATED traceEvent "Use 'Debug.Trace.traceEvent' or 'Debug.Trace.traceEventIO'" #-} 
data SpecConstrAnnotation = NoSpecConstr | ForceSpecConstr
                deriving ( Typeable SpecConstrAnnotation
SpecConstrAnnotation -> Constr
SpecConstrAnnotation -> DataType
(forall b. Data b => b -> b)
-> SpecConstrAnnotation -> SpecConstrAnnotation
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> SpecConstrAnnotation -> u
forall u.
(forall d. Data d => d -> u) -> SpecConstrAnnotation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SpecConstrAnnotation -> m SpecConstrAnnotation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpecConstrAnnotation -> m SpecConstrAnnotation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SpecConstrAnnotation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SpecConstrAnnotation
-> c SpecConstrAnnotation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SpecConstrAnnotation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SpecConstrAnnotation)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpecConstrAnnotation -> m SpecConstrAnnotation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpecConstrAnnotation -> m SpecConstrAnnotation
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpecConstrAnnotation -> m SpecConstrAnnotation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpecConstrAnnotation -> m SpecConstrAnnotation
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SpecConstrAnnotation -> m SpecConstrAnnotation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SpecConstrAnnotation -> m SpecConstrAnnotation
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SpecConstrAnnotation -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SpecConstrAnnotation -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> SpecConstrAnnotation -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SpecConstrAnnotation -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r
gmapT :: (forall b. Data b => b -> b)
-> SpecConstrAnnotation -> SpecConstrAnnotation
$cgmapT :: (forall b. Data b => b -> b)
-> SpecConstrAnnotation -> SpecConstrAnnotation
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SpecConstrAnnotation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SpecConstrAnnotation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SpecConstrAnnotation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SpecConstrAnnotation)
dataTypeOf :: SpecConstrAnnotation -> DataType
$cdataTypeOf :: SpecConstrAnnotation -> DataType
toConstr :: SpecConstrAnnotation -> Constr
$ctoConstr :: SpecConstrAnnotation -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SpecConstrAnnotation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SpecConstrAnnotation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SpecConstrAnnotation
-> c SpecConstrAnnotation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SpecConstrAnnotation
-> c SpecConstrAnnotation
Data 
                         , SpecConstrAnnotation -> SpecConstrAnnotation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool
$c/= :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool
== :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool
$c== :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool
Eq   
                         )
class IsList l where
  
  
  type Item l
  
  
  fromList  :: [Item l] -> l
  
  
  
  
  
  
  fromListN :: Int -> [Item l] -> l
  fromListN Int
_ = forall l. IsList l => [Item l] -> l
fromList
  
  
  toList :: l -> [Item l]
instance IsList [a] where
  type (Item [a]) = a
  fromList :: [Item [a]] -> [a]
fromList = forall a. a -> a
id
  toList :: [a] -> [Item [a]]
toList = forall a. a -> a
id
instance IsList (ZipList a) where
  type Item (ZipList a) = a
  fromList :: [Item (ZipList a)] -> ZipList a
fromList = forall a. [a] -> ZipList a
ZipList
  toList :: ZipList a -> [Item (ZipList a)]
toList = forall a. ZipList a -> [a]
getZipList
instance IsList (NonEmpty a) where
  type Item (NonEmpty a) = a
  fromList :: [Item (NonEmpty a)] -> NonEmpty a
fromList (Item (NonEmpty a)
a:[Item (NonEmpty a)]
as) = Item (NonEmpty a)
a forall a. a -> [a] -> NonEmpty a
:| [Item (NonEmpty a)]
as
  fromList [] = forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NonEmpty.fromList: empty list"
  toList :: NonEmpty a -> [Item (NonEmpty a)]
toList ~(a
a :| [a]
as) = a
a forall a. a -> [a] -> [a]
: [a]
as
instance IsList Version where
  type (Item Version) = Int
  fromList :: [Item Version] -> Version
fromList = [Int] -> Version
makeVersion
  toList :: Version -> [Item Version]
toList = Version -> [Int]
versionBranch
instance IsList CallStack where
  type (Item CallStack) = (String, SrcLoc)
  fromList :: [Item CallStack] -> CallStack
fromList = [([Char], SrcLoc)] -> CallStack
fromCallSiteList
  toList :: CallStack -> [Item CallStack]
toList   = CallStack -> [([Char], SrcLoc)]
getCallStack
atomicModifyMutVar#
  :: MutVar# s a
  -> (a -> b)
  -> State# s
  -> (# State# s, c #)
atomicModifyMutVar# :: forall s a b c.
MutVar# s a -> (a -> b) -> State# s -> (# State# s, c #)
atomicModifyMutVar# MutVar# s a
mv a -> b
f State# s
s =
  case forall a b. a -> b
unsafeCoerce# (forall d a c.
MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #)
atomicModifyMutVar2# MutVar# s a
mv a -> b
f State# s
s) of
    (# State# s
s', Any
_, ~(Any
_, c
res) #) -> (# State# s
s', c
res #)
resizeSmallMutableArray#
  :: SmallMutableArray# s a 
  -> Int# 
  -> a
     
     
  -> State# s
  -> (# State# s, SmallMutableArray# s a #)
resizeSmallMutableArray# :: forall s a.
SmallMutableArray# s a
-> Int# -> a -> State# s -> (# State# s, SmallMutableArray# s a #)
resizeSmallMutableArray# SmallMutableArray# s a
arr0 Int#
szNew a
a State# s
s0 =
  case forall d a.
SmallMutableArray# d a -> State# d -> (# State# d, Int# #)
getSizeofSmallMutableArray# SmallMutableArray# s a
arr0 State# s
s0 of
    (# State# s
s1, Int#
szOld #) -> if Int# -> Bool
isTrue# (Int#
szNew Int# -> Int# -> Int#
<# Int#
szOld)
      then case forall d a. SmallMutableArray# d a -> Int# -> State# d -> State# d
shrinkSmallMutableArray# SmallMutableArray# s a
arr0 Int#
szNew State# s
s1 of
        State# s
s2 -> (# State# s
s2, SmallMutableArray# s a
arr0 #)
      else if Int# -> Bool
isTrue# (Int#
szNew Int# -> Int# -> Int#
># Int#
szOld)
        then case forall a d.
Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #)
newSmallArray# Int#
szNew a
a State# s
s1 of
          (# State# s
s2, SmallMutableArray# s a
arr1 #) -> case forall d a.
SmallMutableArray# d a
-> Int#
-> SmallMutableArray# d a
-> Int#
-> Int#
-> State# d
-> State# d
copySmallMutableArray# SmallMutableArray# s a
arr0 Int#
0# SmallMutableArray# s a
arr1 Int#
0# Int#
szOld State# s
s2 of
            State# s
s3 -> (# State# s
s3, SmallMutableArray# s a
arr1 #)
        else (# State# s
s1, SmallMutableArray# s a
arr0 #)
considerAccessible :: Bool
considerAccessible :: Bool
considerAccessible = Bool
True