{-# LANGUAGE Unsafe #-}
{-# LANGUAGE MagicHash, UnboxedTuples, TypeFamilies, DeriveDataTypeable,
MultiParamTypeClasses, FlexibleInstances, NoImplicitPrelude #-}
module GHC.Exts
(
Int(..),Word(..),Float(..),Double(..),
Char(..),
Ptr(..), FunPtr(..),
maxTupleSize,
module GHC.Prim,
shiftL#, shiftRL#, iShiftL#, iShiftRA#, iShiftRL#,
uncheckedShiftL64#, uncheckedShiftRL64#,
uncheckedIShiftL64#, uncheckedIShiftRA64#,
isTrue#,
atomicModifyMutVar#,
build, augment,
IsString(..),
breakpoint, breakpointCond,
lazy, inline, oneShot,
runRW#,
Data.Coerce.coerce, Data.Coerce.Coercible,
type (~~),
GHC.Prim.TYPE, RuntimeRep(..), VecCount(..), VecElem(..),
Down(..), groupWith, sortWith, the,
traceEvent,
SpecConstrAnnotation(..),
currentCallStack,
Constraint,
Any,
IsList(..)
) where
import GHC.Prim hiding ( coerce, TYPE )
import qualified GHC.Prim
import GHC.Base hiding ( coerce )
import GHC.Word
import GHC.Int
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
maxTupleSize :: Int
maxTupleSize :: Int
maxTupleSize = 62
the :: Eq a => [a] -> a
the :: [a] -> a
the (x :: a
x:xs :: [a]
xs)
| (a -> Bool) -> [a] -> Bool
forall a. (a -> Bool) -> [a] -> Bool
all (a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
==) [a]
xs = a
x
| Bool
otherwise = [Char] -> a
forall a. [Char] -> a
errorWithoutStackTrace "GHC.Exts.the: non-identical elements"
the [] = [Char] -> a
forall a. [Char] -> a
errorWithoutStackTrace "GHC.Exts.the: empty list"
sortWith :: Ord b => (a -> b) -> [a] -> [a]
sortWith :: (a -> b) -> [a] -> [a]
sortWith f :: a -> b
f = (a -> a -> Ordering) -> [a] -> [a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (\x :: a
x y :: a
y -> b -> b -> Ordering
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 :: (a -> b) -> [a] -> [[a]]
groupWith f :: a -> b
f xs :: [a]
xs = (forall b. ([a] -> b -> b) -> b -> b) -> [[a]]
forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build (\c :: [a] -> b -> b
c n :: b
n -> ([a] -> b -> b) -> b -> (a -> a -> Bool) -> [a] -> b
forall a lst.
([a] -> lst -> lst) -> lst -> (a -> a -> Bool) -> [a] -> lst
groupByFB [a] -> b -> b
c b
n (\x :: a
x y :: a
y -> a -> b
f a
x b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== a -> b
f a
y) ((a -> b) -> [a] -> [a]
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 :: ([a] -> lst -> lst) -> lst -> (a -> a -> Bool) -> [a] -> lst
groupByFB c :: [a] -> lst -> lst
c n :: lst
n eq :: a -> a -> Bool
eq xs0 :: [a]
xs0 = [a] -> lst
groupByFBCore [a]
xs0
where groupByFBCore :: [a] -> lst
groupByFBCore [] = lst
n
groupByFBCore (x :: a
x:xs :: [a]
xs) = [a] -> lst -> lst
c (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ys) ([a] -> lst
groupByFBCore [a]
zs)
where (ys :: [a]
ys, zs :: [a]
zs) = (a -> Bool) -> [a] -> ([a], [a])
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 ( Data
, Eq
)
class IsList l where
type Item l
fromList :: [Item l] -> l
fromListN :: Int -> [Item l] -> l
fromListN _ = [Item l] -> l
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 = [Item [a]] -> [a]
forall a. a -> a
id
toList :: [a] -> [Item [a]]
toList = [a] -> [Item [a]]
forall a. a -> a
id
instance IsList (NonEmpty a) where
type Item (NonEmpty a) = a
fromList :: [Item (NonEmpty a)] -> NonEmpty a
fromList (a :: Item (NonEmpty a)
a:as :: [Item (NonEmpty a)]
as) = a
Item (NonEmpty a)
a a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
[Item (NonEmpty a)]
as
fromList [] = [Char] -> NonEmpty a
forall a. [Char] -> a
errorWithoutStackTrace "NonEmpty.fromList: empty list"
toList :: NonEmpty a -> [Item (NonEmpty a)]
toList ~(a :: a
a :| as :: [a]
as) = a
a a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
as
instance IsList Version where
type (Item Version) = Int
fromList :: [Item Version] -> Version
fromList = [Int] -> Version
[Item Version] -> Version
makeVersion
toList :: Version -> [Item Version]
toList = Version -> [Int]
Version -> [Item Version]
versionBranch
instance IsList CallStack where
type (Item CallStack) = (String, SrcLoc)
fromList :: [Item CallStack] -> CallStack
fromList = [([Char], SrcLoc)] -> CallStack
[Item CallStack] -> CallStack
fromCallSiteList
toList :: CallStack -> [Item CallStack]
toList = CallStack -> [([Char], SrcLoc)]
CallStack -> [Item CallStack]
getCallStack
atomicModifyMutVar#
:: MutVar# s a
-> (a -> b)
-> State# s
-> (# State# s, c #)
atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (# State# s, c #)
atomicModifyMutVar# mv :: MutVar# s a
mv f :: a -> b
f s :: State# s
s =
case (# State# s, a, b #) -> (# State# s, Any, (Any, c) #)
unsafeCoerce# (MutVar# s a -> (a -> b) -> State# s -> (# State# s, a, b #)
forall d a b.
MutVar# d a -> (a -> b) -> State# d -> (# State# d, a, b #)
atomicModifyMutVar2# MutVar# s a
mv a -> b
f State# s
s) of
(# s' :: State# s
s', _, ~(_, res :: c
res) #) -> (# State# s
s', c
res #)