base-4.14.1.0: Basic libraries
Copyright(c) The University of Glasgow 2002
Licensesee libraries/base/LICENSE
Maintainercvs-ghc@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellUnsafe
LanguageHaskell2010

GHC.Exts

Description

GHC Extensions: this is the Approved Way to get at GHC-specific extensions.

Note: no other base module should import this module.

Synopsis

Representations of some basic types

data Int #

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

Constructors

I# Int# 

Instances

Instances details
Bounded Int Source #

Since: 2.1

Instance details

Defined in GHC.Enum

Enum Int Source #

Since: 2.1

Instance details

Defined in GHC.Enum

Eq Int 
Instance details

Defined in GHC.Classes

Methods

(==) :: Int -> Int -> Bool #

(/=) :: Int -> Int -> Bool #

Integral Int Source #

Since: 2.0.1

Instance details

Defined in GHC.Real

Methods

quot :: Int -> Int -> Int Source #

rem :: Int -> Int -> Int Source #

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

quotRem :: Int -> Int -> (Int, Int) Source #

divMod :: Int -> Int -> (Int, Int) Source #

toInteger :: Int -> Integer Source #

Data Int Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int Source #

toConstr :: Int -> Constr Source #

dataTypeOf :: Int -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) Source #

gmapT :: (forall b. Data b => b -> b) -> Int -> Int Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source #

Num Int Source #

Since: 2.1

Instance details

Defined in GHC.Num

Ord Int 
Instance details

Defined in GHC.Classes

Methods

compare :: Int -> Int -> Ordering #

(<) :: Int -> Int -> Bool #

(<=) :: Int -> Int -> Bool #

(>) :: Int -> Int -> Bool #

(>=) :: Int -> Int -> Bool #

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Read Int Source #

Since: 2.1

Instance details

Defined in GHC.Read

Real Int Source #

Since: 2.0.1

Instance details

Defined in GHC.Real

Show Int Source #

Since: 2.1

Instance details

Defined in GHC.Show

Ix Int Source #

Since: 2.1

Instance details

Defined in GHC.Ix

FiniteBits Int Source #

Since: 4.6.0.0

Instance details

Defined in Data.Bits

Bits Int Source #

Since: 2.1

Instance details

Defined in Data.Bits

Storable Int Source #

Since: 2.1

Instance details

Defined in Foreign.Storable

PrintfArg Int Source #

Since: 2.1

Instance details

Defined in Text.Printf

Generic1 (URec Int :: k -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Int) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Int a -> Rep1 (URec Int) a Source #

to1 :: forall (a :: k0). Rep1 (URec Int) a -> URec Int a Source #

Foldable (UInt :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UInt m -> m Source #

foldMap :: Monoid m => (a -> m) -> UInt a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source #

foldr :: (a -> b -> b) -> b -> UInt a -> b Source #

foldr' :: (a -> b -> b) -> b -> UInt a -> b Source #

foldl :: (b -> a -> b) -> b -> UInt a -> b Source #

foldl' :: (b -> a -> b) -> b -> UInt a -> b Source #

foldr1 :: (a -> a -> a) -> UInt a -> a Source #

foldl1 :: (a -> a -> a) -> UInt a -> a Source #

toList :: UInt a -> [a] Source #

null :: UInt a -> Bool Source #

length :: UInt a -> Int Source #

elem :: Eq a => a -> UInt a -> Bool Source #

maximum :: Ord a => UInt a -> a Source #

minimum :: Ord a => UInt a -> a Source #

sum :: Num a => UInt a -> a Source #

product :: Num a => UInt a -> a Source #

Traversable (UInt :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UInt a -> f (UInt b) Source #

sequenceA :: Applicative f => UInt (f a) -> f (UInt a) Source #

mapM :: Monad m => (a -> m b) -> UInt a -> m (UInt b) Source #

sequence :: Monad m => UInt (m a) -> m (UInt a) Source #

Functor (URec Int :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b Source #

(<$) :: a -> URec Int b -> URec Int a Source #

Eq (URec Int p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Ord (URec Int p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Int p -> URec Int p -> Ordering #

(<) :: URec Int p -> URec Int p -> Bool #

(<=) :: URec Int p -> URec Int p -> Bool #

(>) :: URec Int p -> URec Int p -> Bool #

(>=) :: URec Int p -> URec Int p -> Bool #

max :: URec Int p -> URec Int p -> URec Int p #

min :: URec Int p -> URec Int p -> URec Int p #

Show (URec Int p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Generic (URec Int p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type Source #

Methods

from :: URec Int p -> Rep (URec Int p) x Source #

to :: Rep (URec Int p) x -> URec Int p Source #

data URec Int (p :: k) Source #

Used for marking occurrences of Int#

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

data URec Int (p :: k) = UInt {}
type Rep1 (URec Int :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

type Rep1 (URec Int :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: k -> Type)))
type Rep (URec Int p) Source # 
Instance details

Defined in GHC.Generics

type Rep (URec Int p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type)))

data Word #

A Word is an unsigned integral type, with the same size as Int.

Constructors

W# Word# 

Instances

Instances details
Bounded Word Source #

Since: 2.1

Instance details

Defined in GHC.Enum

Enum Word Source #

Since: 2.1

Instance details

Defined in GHC.Enum

Eq Word 
Instance details

Defined in GHC.Classes

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Integral Word Source #

Since: 2.1

Instance details

Defined in GHC.Real

Data Word Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word Source #

toConstr :: Word -> Constr Source #

dataTypeOf :: Word -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) Source #

gmapT :: (forall b. Data b => b -> b) -> Word -> Word Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source #

Num Word Source #

Since: 2.1

Instance details

Defined in GHC.Num

Ord Word 
Instance details

Defined in GHC.Classes

Methods

compare :: Word -> Word -> Ordering #

(<) :: Word -> Word -> Bool #

(<=) :: Word -> Word -> Bool #

(>) :: Word -> Word -> Bool #

(>=) :: Word -> Word -> Bool #

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Read Word Source #

Since: 4.5.0.0

Instance details

Defined in GHC.Read

Real Word Source #

Since: 2.1

Instance details

Defined in GHC.Real

Show Word Source #

Since: 2.1

Instance details

Defined in GHC.Show

Ix Word Source #

Since: 4.6.0.0

Instance details

Defined in GHC.Ix

FiniteBits Word Source #

Since: 4.6.0.0

Instance details

Defined in Data.Bits

Bits Word Source #

Since: 2.1

Instance details

Defined in Data.Bits

Storable Word Source #

Since: 2.1

Instance details

Defined in Foreign.Storable

PrintfArg Word Source #

Since: 2.1

Instance details

Defined in Text.Printf

Generic1 (URec Word :: k -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Word) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Word a -> Rep1 (URec Word) a Source #

to1 :: forall (a :: k0). Rep1 (URec Word) a -> URec Word a Source #

Foldable (UWord :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UWord m -> m Source #

foldMap :: Monoid m => (a -> m) -> UWord a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source #

foldr :: (a -> b -> b) -> b -> UWord a -> b Source #

foldr' :: (a -> b -> b) -> b -> UWord a -> b Source #

foldl :: (b -> a -> b) -> b -> UWord a -> b Source #

foldl' :: (b -> a -> b) -> b -> UWord a -> b Source #

foldr1 :: (a -> a -> a) -> UWord a -> a Source #

foldl1 :: (a -> a -> a) -> UWord a -> a Source #

toList :: UWord a -> [a] Source #

null :: UWord a -> Bool Source #

length :: UWord a -> Int Source #

elem :: Eq a => a -> UWord a -> Bool Source #

maximum :: Ord a => UWord a -> a Source #

minimum :: Ord a => UWord a -> a Source #

sum :: Num a => UWord a -> a Source #

product :: Num a => UWord a -> a Source #

Traversable (UWord :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UWord a -> f (UWord b) Source #

sequenceA :: Applicative f => UWord (f a) -> f (UWord a) Source #

mapM :: Monad m => (a -> m b) -> UWord a -> m (UWord b) Source #

sequence :: Monad m => UWord (m a) -> m (UWord a) Source #

Functor (URec Word :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b Source #

(<$) :: a -> URec Word b -> URec Word a Source #

Eq (URec Word p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Show (URec Word p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Generic (URec Word p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type Source #

Methods

from :: URec Word p -> Rep (URec Word p) x Source #

to :: Rep (URec Word p) x -> URec Word p Source #

data URec Word (p :: k) Source #

Used for marking occurrences of Word#

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

data URec Word (p :: k) = UWord {}
type Rep1 (URec Word :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

type Rep1 (URec Word :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: k -> Type)))
type Rep (URec Word p) Source # 
Instance details

Defined in GHC.Generics

type Rep (URec Word p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: Type -> Type)))

data Float #

Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.

Constructors

F# Float# 

Instances

Instances details
Enum Float Source #

Since: 2.1

Instance details

Defined in GHC.Float

Eq Float

Note that due to the presence of NaN, Float's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Float)
False

Also note that Float's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Methods

(==) :: Float -> Float -> Bool #

(/=) :: Float -> Float -> Bool #

Floating Float Source #

Since: 2.1

Instance details

Defined in GHC.Float

Fractional Float Source #

Note that due to the presence of NaN, not all elements of Float have an multiplicative inverse.

>>> 0/0 * (recip 0/0 :: Float)
NaN

Since: 2.1

Instance details

Defined in GHC.Float

Data Float Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float Source #

toConstr :: Float -> Constr Source #

dataTypeOf :: Float -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) Source #

gmapT :: (forall b. Data b => b -> b) -> Float -> Float Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source #

Num Float Source #

Note that due to the presence of NaN, not all elements of Float have an additive inverse.

>>> 0/0 + (negate 0/0 :: Float)
NaN

Also note that due to the presence of -0, Float's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Float)
0.0

Since: 2.1

Instance details

Defined in GHC.Float

Ord Float

Note that due to the presence of NaN, Float's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Float)
False

Also note that, due to the same, Ord's operator interactions are not respected by Float's instance:

>>> (0/0 :: Float) > 1
False
>>> compare (0/0 :: Float) 1
GT
Instance details

Defined in GHC.Classes

Methods

compare :: Float -> Float -> Ordering #

(<) :: Float -> Float -> Bool #

(<=) :: Float -> Float -> Bool #

(>) :: Float -> Float -> Bool #

(>=) :: Float -> Float -> Bool #

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Read Float Source #

Since: 2.1

Instance details

Defined in GHC.Read

Real Float Source #

Since: 2.1

Instance details

Defined in GHC.Float

RealFloat Float Source #

Since: 2.1

Instance details

Defined in GHC.Float

RealFrac Float Source #

Since: 2.1

Instance details

Defined in GHC.Float

Methods

properFraction :: Integral b => Float -> (b, Float) Source #

truncate :: Integral b => Float -> b Source #

round :: Integral b => Float -> b Source #

ceiling :: Integral b => Float -> b Source #

floor :: Integral b => Float -> b Source #

Show Float Source #

Since: 2.1

Instance details

Defined in GHC.Float

Storable Float Source #

Since: 2.1

Instance details

Defined in Foreign.Storable

PrintfArg Float Source #

Since: 2.1

Instance details

Defined in Text.Printf

Generic1 (URec Float :: k -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Float) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Float a -> Rep1 (URec Float) a Source #

to1 :: forall (a :: k0). Rep1 (URec Float) a -> URec Float a Source #

Foldable (UFloat :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UFloat m -> m Source #

foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source #

foldr :: (a -> b -> b) -> b -> UFloat a -> b Source #

foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source #

foldl :: (b -> a -> b) -> b -> UFloat a -> b Source #

foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source #

foldr1 :: (a -> a -> a) -> UFloat a -> a Source #

foldl1 :: (a -> a -> a) -> UFloat a -> a Source #

toList :: UFloat a -> [a] Source #

null :: UFloat a -> Bool Source #

length :: UFloat a -> Int Source #

elem :: Eq a => a -> UFloat a -> Bool Source #

maximum :: Ord a => UFloat a -> a Source #

minimum :: Ord a => UFloat a -> a Source #

sum :: Num a => UFloat a -> a Source #

product :: Num a => UFloat a -> a Source #

Traversable (UFloat :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UFloat a -> f (UFloat b) Source #

sequenceA :: Applicative f => UFloat (f a) -> f (UFloat a) Source #

mapM :: Monad m => (a -> m b) -> UFloat a -> m (UFloat b) Source #

sequence :: Monad m => UFloat (m a) -> m (UFloat a) Source #

Functor (URec Float :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b Source #

(<$) :: a -> URec Float b -> URec Float a Source #

Eq (URec Float p) Source # 
Instance details

Defined in GHC.Generics

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) Source # 
Instance details

Defined in GHC.Generics

Methods

compare :: URec Float p -> URec Float p -> Ordering #

(<) :: URec Float p -> URec Float p -> Bool #

(<=) :: URec Float p -> URec Float p -> Bool #

(>) :: URec Float p -> URec Float p -> Bool #

(>=) :: URec Float p -> URec Float p -> Bool #

max :: URec Float p -> URec Float p -> URec Float p #

min :: URec Float p -> URec Float p -> URec Float p #

Show (URec Float p) Source # 
Instance details

Defined in GHC.Generics

Generic (URec Float p) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type Source #

Methods

from :: URec Float p -> Rep (URec Float p) x Source #

to :: Rep (URec Float p) x -> URec Float p Source #

data URec Float (p :: k) Source #

Used for marking occurrences of Float#

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

data URec Float (p :: k) = UFloat {}
type Rep1 (URec Float :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: k -> Type)))
type Rep (URec Float p) Source # 
Instance details

Defined in GHC.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type)))

data Double #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Constructors

D# Double# 

Instances

Instances details
Enum Double Source #

Since: 2.1

Instance details

Defined in GHC.Float

Eq Double

Note that due to the presence of NaN, Double's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Double)
False

Also note that Double's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Methods

(==) :: Double -> Double -> Bool #

(/=) :: Double -> Double -> Bool #

Floating Double Source #

Since: 2.1

Instance details

Defined in GHC.Float

Fractional Double Source #

Note that due to the presence of NaN, not all elements of Double have an multiplicative inverse.

>>> 0/0 * (recip 0/0 :: Double)
NaN

Since: 2.1

Instance details

Defined in GHC.Float

Data Double Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double Source #

toConstr :: Double -> Constr Source #

dataTypeOf :: Double -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) Source #

gmapT :: (forall b. Data b => b -> b) -> Double -> Double Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source #

Num Double Source #

Note that due to the presence of NaN, not all elements of Double have an additive inverse.

>>> 0/0 + (negate 0/0 :: Double)
NaN

Also note that due to the presence of -0, Double's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Double)
0.0

Since: 2.1

Instance details

Defined in GHC.Float

Ord Double

Note that due to the presence of NaN, Double's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Double)
False

Also note that, due to the same, Ord's operator interactions are not respected by Double's instance:

>>> (0/0 :: Double) > 1
False
>>> compare (0/0 :: Double) 1
GT
Instance details

Defined in GHC.Classes

Read Double Source #

Since: 2.1

Instance details

Defined in GHC.Read

Real Double Source #

Since: 2.1

Instance details

Defined in GHC.Float

RealFloat Double Source #

Since: 2.1

Instance details

Defined in GHC.Float

RealFrac Double Source #

Since: 2.1

Instance details

Defined in GHC.Float

Show Double Source #

Since: 2.1

Instance details

Defined in GHC.Float

Storable Double Source #

Since: 2.1

Instance details

Defined in Foreign.Storable

PrintfArg Double Source #

Since: 2.1

Instance details

Defined in Text.Printf

Generic1 (URec Double :: k -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Double) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Double a -> Rep1 (URec Double) a Source #

to1 :: forall (a :: k0). Rep1 (URec Double) a -> URec Double a Source #

Foldable (UDouble :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UDouble m -> m Source #

foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source #

foldr :: (a -> b -> b) -> b -> UDouble a -> b Source #

foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source #

foldl :: (b -> a -> b) -> b -> UDouble a -> b Source #

foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source #

foldr1 :: (a -> a -> a) -> UDouble a -> a Source #

foldl1 :: (a -> a -> a) -> UDouble a -> a Source #

toList :: UDouble a -> [a] Source #

null :: UDouble a -> Bool Source #

length :: UDouble a -> Int Source #

elem :: Eq a => a -> UDouble a -> Bool Source #

maximum :: Ord a => UDouble a -> a Source #

minimum :: Ord a => UDouble a -> a Source #

sum :: Num a => UDouble a -> a Source #

product :: Num a => UDouble a -> a Source #

Traversable (UDouble :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UDouble a -> f (UDouble b) Source #

sequenceA :: Applicative f => UDouble (f a) -> f (UDouble a) Source #

mapM :: Monad m => (a -> m b) -> UDouble a -> m (UDouble b) Source #

sequence :: Monad m => UDouble (m a) -> m (UDouble a) Source #

Functor (URec Double :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b Source #

(<$) :: a -> URec Double b -> URec Double a Source #

Eq (URec Double p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Double p -> URec Double p -> Ordering #

(<) :: URec Double p -> URec Double p -> Bool #

(<=) :: URec Double p -> URec Double p -> Bool #

(>) :: URec Double p -> URec Double p -> Bool #

(>=) :: URec Double p -> URec Double p -> Bool #

max :: URec Double p -> URec Double p -> URec Double p #

min :: URec Double p -> URec Double p -> URec Double p #

Show (URec Double p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Generic (URec Double p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type Source #

Methods

from :: URec Double p -> Rep (URec Double p) x Source #

to :: Rep (URec Double p) x -> URec Double p Source #

data URec Double (p :: k) Source #

Used for marking occurrences of Double#

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

data URec Double (p :: k) = UDouble {}
type Rep1 (URec Double :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: k -> Type)))
type Rep (URec Double p) Source # 
Instance details

Defined in GHC.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

data Char #

The character type Char is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see http://www.unicode.org/ for details). This set extends the ISO 8859-1 (Latin-1) character set (the first 256 characters), which is itself an extension of the ASCII character set (the first 128 characters). A character literal in Haskell has type Char.

To convert a Char to or from the corresponding Int value defined by Unicode, use toEnum and fromEnum from the Enum class respectively (or equivalently ord and chr).

Constructors

C# Char# 

Instances

Instances details
Bounded Char Source #

Since: 2.1

Instance details

Defined in GHC.Enum

Enum Char Source #

Since: 2.1

Instance details

Defined in GHC.Enum

Eq Char 
Instance details

Defined in GHC.Classes

Methods

(==) :: Char -> Char -> Bool #

(/=) :: Char -> Char -> Bool #

Data Char Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char Source #

toConstr :: Char -> Constr Source #

dataTypeOf :: Char -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) Source #

gmapT :: (forall b. Data b => b -> b) -> Char -> Char Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source #

Ord Char 
Instance details

Defined in GHC.Classes

Methods

compare :: Char -> Char -> Ordering #

(<) :: Char -> Char -> Bool #

(<=) :: Char -> Char -> Bool #

(>) :: Char -> Char -> Bool #

(>=) :: Char -> Char -> Bool #

max :: Char -> Char -> Char #

min :: Char -> Char -> Char #

Read Char Source #

Since: 2.1

Instance details

Defined in GHC.Read

Show Char Source #

Since: 2.1

Instance details

Defined in GHC.Show

Ix Char Source #

Since: 2.1

Instance details

Defined in GHC.Ix

Storable Char Source #

Since: 2.1

Instance details

Defined in Foreign.Storable

IsChar Char Source #

Since: 2.1

Instance details

Defined in Text.Printf

PrintfArg Char Source #

Since: 2.1

Instance details

Defined in Text.Printf

Generic1 (URec Char :: k -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Char) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Char a -> Rep1 (URec Char) a Source #

to1 :: forall (a :: k0). Rep1 (URec Char) a -> URec Char a Source #

Foldable (UChar :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UChar m -> m Source #

foldMap :: Monoid m => (a -> m) -> UChar a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source #

foldr :: (a -> b -> b) -> b -> UChar a -> b Source #

foldr' :: (a -> b -> b) -> b -> UChar a -> b Source #

foldl :: (b -> a -> b) -> b -> UChar a -> b Source #

foldl' :: (b -> a -> b) -> b -> UChar a -> b Source #

foldr1 :: (a -> a -> a) -> UChar a -> a Source #

foldl1 :: (a -> a -> a) -> UChar a -> a Source #

toList :: UChar a -> [a] Source #

null :: UChar a -> Bool Source #

length :: UChar a -> Int Source #

elem :: Eq a => a -> UChar a -> Bool Source #

maximum :: Ord a => UChar a -> a Source #

minimum :: Ord a => UChar a -> a Source #

sum :: Num a => UChar a -> a Source #

product :: Num a => UChar a -> a Source #

Traversable (UChar :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UChar a -> f (UChar b) Source #

sequenceA :: Applicative f => UChar (f a) -> f (UChar a) Source #

mapM :: Monad m => (a -> m b) -> UChar a -> m (UChar b) Source #

sequence :: Monad m => UChar (m a) -> m (UChar a) Source #

Functor (URec Char :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b Source #

(<$) :: a -> URec Char b -> URec Char a Source #

Eq (URec Char p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Char p -> URec Char p -> Bool #

(/=) :: URec Char p -> URec Char p -> Bool #

Ord (URec Char p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Char p -> URec Char p -> Ordering #

(<) :: URec Char p -> URec Char p -> Bool #

(<=) :: URec Char p -> URec Char p -> Bool #

(>) :: URec Char p -> URec Char p -> Bool #

(>=) :: URec Char p -> URec Char p -> Bool #

max :: URec Char p -> URec Char p -> URec Char p #

min :: URec Char p -> URec Char p -> URec Char p #

Show (URec Char p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Generic (URec Char p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type Source #

Methods

from :: URec Char p -> Rep (URec Char p) x Source #

to :: Rep (URec Char p) x -> URec Char p Source #

data URec Char (p :: k) Source #

Used for marking occurrences of Char#

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

data URec Char (p :: k) = UChar {}
type Rep1 (URec Char :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

type Rep1 (URec Char :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: k -> Type)))
type Rep (URec Char p) Source # 
Instance details

Defined in GHC.Generics

type Rep (URec Char p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: Type -> Type)))

data Ptr a Source #

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

The type a will often be an instance of class Storable which provides the marshalling operations. However this is not essential, and you can provide your own operations to access the pointer. For example you might write small foreign functions to get or set the fields of a C struct.

Constructors

Ptr Addr# 

Instances

Instances details
Generic1 (URec (Ptr ()) :: k -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec (Ptr ())) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a Source #

to1 :: forall (a :: k0). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a Source #

Eq (Ptr a) Source #

Since: 2.1

Instance details

Defined in GHC.Ptr

Methods

(==) :: Ptr a -> Ptr a -> Bool #

(/=) :: Ptr a -> Ptr a -> Bool #

Data a => Data (Ptr a) Source #

Since: 4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) Source #

toConstr :: Ptr a -> Constr Source #

dataTypeOf :: Ptr a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

Ord (Ptr a) Source #

Since: 2.1

Instance details

Defined in GHC.Ptr

Methods

compare :: Ptr a -> Ptr a -> Ordering #

(<) :: Ptr a -> Ptr a -> Bool #

(<=) :: Ptr a -> Ptr a -> Bool #

(>) :: Ptr a -> Ptr a -> Bool #

(>=) :: Ptr a -> Ptr a -> Bool #

max :: Ptr a -> Ptr a -> Ptr a #

min :: Ptr a -> Ptr a -> Ptr a #

Show (Ptr a) Source #

Since: 2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS Source #

show :: Ptr a -> String Source #

showList :: [Ptr a] -> ShowS Source #

Foldable (UAddr :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UAddr m -> m Source #

foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source #

foldr :: (a -> b -> b) -> b -> UAddr a -> b Source #

foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source #

foldl :: (b -> a -> b) -> b -> UAddr a -> b Source #

foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source #

foldr1 :: (a -> a -> a) -> UAddr a -> a Source #

foldl1 :: (a -> a -> a) -> UAddr a -> a Source #

toList :: UAddr a -> [a] Source #

null :: UAddr a -> Bool Source #

length :: UAddr a -> Int Source #

elem :: Eq a => a -> UAddr a -> Bool Source #

maximum :: Ord a => UAddr a -> a Source #

minimum :: Ord a => UAddr a -> a Source #

sum :: Num a => UAddr a -> a Source #

product :: Num a => UAddr a -> a Source #

Traversable (UAddr :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) Source #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) Source #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) Source #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) Source #

Storable (Ptr a) Source #

Since: 2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int Source #

alignment :: Ptr a -> Int Source #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) Source #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) Source #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () Source #

peek :: Ptr (Ptr a) -> IO (Ptr a) Source #

poke :: Ptr (Ptr a) -> Ptr a -> IO () Source #

Functor (URec (Ptr ()) :: Type -> Type) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Source #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a Source #

Eq (URec (Ptr ()) p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

Ord (URec (Ptr ()) p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

Generic (URec (Ptr ()) p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type Source #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x Source #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p Source #

data URec (Ptr ()) (p :: k) Source #

Used for marking occurrences of Addr#

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p) Source # 
Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

data FunPtr a Source #

A value of type FunPtr a is a pointer to a function callable from foreign code. The type a will normally be a foreign type, a function type with zero or more arguments where

A value of type FunPtr a may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import like

foreign import ccall "stdlib.h &free"
  p_free :: FunPtr (Ptr a -> IO ())

or a pointer to a Haskell function created using a wrapper stub declared to produce a FunPtr of the correct type. For example:

type Compare = Int -> Int -> Bool
foreign import ccall "wrapper"
  mkCompare :: Compare -> IO (FunPtr Compare)

Calls to wrapper stubs like mkCompare allocate storage, which should be released with freeHaskellFunPtr when no longer required.

To convert FunPtr values to corresponding Haskell functions, one can define a dynamic stub for the specific foreign type, e.g.

type IntFunction = CInt -> IO ()
foreign import ccall "dynamic"
  mkFun :: FunPtr IntFunction -> IntFunction

Constructors

FunPtr Addr# 

Instances

Instances details
Eq (FunPtr a) Source # 
Instance details

Defined in GHC.Ptr

Methods

(==) :: FunPtr a -> FunPtr a -> Bool #

(/=) :: FunPtr a -> FunPtr a -> Bool #

Ord (FunPtr a) Source # 
Instance details

Defined in GHC.Ptr

Methods

compare :: FunPtr a -> FunPtr a -> Ordering #

(<) :: FunPtr a -> FunPtr a -> Bool #

(<=) :: FunPtr a -> FunPtr a -> Bool #

(>) :: FunPtr a -> FunPtr a -> Bool #

(>=) :: FunPtr a -> FunPtr a -> Bool #

max :: FunPtr a -> FunPtr a -> FunPtr a #

min :: FunPtr a -> FunPtr a -> FunPtr a #

Show (FunPtr a) Source #

Since: 2.1

Instance details

Defined in GHC.Ptr

Storable (FunPtr a) Source #

Since: 2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int Source #

alignment :: FunPtr a -> Int Source #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) Source #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) Source #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () Source #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) Source #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () Source #

The maximum tuple size

Primitive operations

seq :: forall (r :: RuntimeRep) a (b :: TYPE r). a -> b -> b infixr 0 #

The value of seq a b is bottom if a is bottom, and otherwise equal to b. In other words, it evaluates the first argument a to weak head normal form (WHNF). seq is usually introduced to improve performance by avoiding unneeded laziness.

A note on evaluation order: the expression seq a b does not guarantee that a will be evaluated before b. The only guarantee given by seq is that the both a and b will be evaluated before seq returns a value. In particular, this means that b may be evaluated before a. If you need to guarantee a specific order of evaluation, you must use the function pseq from the "parallel" package.

unsafeCoerce# :: forall (k0 :: RuntimeRep) (k1 :: RuntimeRep) (a :: TYPE k0) (b :: TYPE k1). a -> b #

The function unsafeCoerce# allows you to side-step the typechecker entirely. That is, it allows you to coerce any type into any other type. If you use this function, you had better get it right, otherwise segmentation faults await. It is generally used when you want to write a program that you know is well-typed, but where Haskell's type system is not expressive enough to prove that it is well typed.

The following uses of unsafeCoerce# are supposed to work (i.e. not lead to spurious compile-time or run-time crashes):

  • Casting any lifted type to Any
  • Casting Any back to the real type
  • Casting an unboxed type to another unboxed type of the same size. (Casting between floating-point and integral types does not work. See the GHC.Float module for functions to do work.)
  • Casting between two types that have the same runtime representation. One case is when the two types differ only in "phantom" type parameters, for example Ptr Int to Ptr Float, or [Int] to [Float] when the list is known to be empty. Also, a newtype of a type T has the same representation at runtime as T.

Other uses of unsafeCoerce# are undefined. In particular, you should not use unsafeCoerce# to cast a T to an algebraic data type D, unless T is also an algebraic data type. For example, do not cast Int->Int to Bool, even if you later cast that Bool back to Int->Int before applying it. The reasons have to do with GHC's internal representation details (for the cognoscenti, data values can be entered but function closures cannot). If you want a safe type to cast things to, use Any, which is not an algebraic data type.

Warning: this can fail with an unchecked exception.

nullAddr# :: Addr# #

The null address.

proxy# :: forall k (a :: k). Proxy# a #

Witness for an unboxed Proxy# value, which has no runtime representation.

data Addr# :: TYPE 'AddrRep #

An arbitrary machine address assumed to point outside the garbage-collected heap.

data Char# :: TYPE 'WordRep #

data Int# :: TYPE 'IntRep #

data Int8# :: TYPE 'Int8Rep #

data Weak# a :: TYPE 'UnliftedRep #

data MVar# a b :: TYPE 'UnliftedRep #

A shared mutable variable (not the same as a MutVar#!). (Note: in a non-concurrent implementation, (MVar# a) can be represented by (MutVar# (Maybe a)).)

data RealWorld #

RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.

data State# a :: TYPE ('TupleRep ('[] :: [RuntimeRep])) #

State# is the primitive, unlifted type of states. It has one type parameter, thus State# RealWorld, or State# s, where s is a type variable. The only purpose of the type parameter is to keep different state threads separate. It is represented by nothing at all.

data MutVar# a b :: TYPE 'UnliftedRep #

A MutVar# behaves like a single-element mutable array.

data Void# :: TYPE ('TupleRep ('[] :: [RuntimeRep])) #

data Word# :: TYPE 'WordRep #

data ThreadId# :: TYPE 'UnliftedRep #

(In a non-concurrent implementation, this can be a singleton type, whose (unique) value is returned by myThreadId#. The other operations can be omitted.)

data BCO# :: TYPE 'UnliftedRep #

Primitive bytecode type.

data TVar# a b :: TYPE 'UnliftedRep #

data Proxy# (a :: k) :: TYPE ('TupleRep ('[] :: [RuntimeRep])) #

The type constructor Proxy# is used to bear witness to some type variable. It's used when you want to pass around proxy values for doing things like modelling type applications. A Proxy# is not only unboxed, it also has a polymorphic kind, and has no runtime representation, being totally free.

data Int8X16# :: TYPE ('VecRep 'Vec16 'Int8ElemRep) #

Warning: this is only available on LLVM.

data Int16X8# :: TYPE ('VecRep 'Vec8 'Int16ElemRep) #

Warning: this is only available on LLVM.

data Int32X4# :: TYPE ('VecRep 'Vec4 'Int32ElemRep) #

Warning: this is only available on LLVM.

data Int64X2# :: TYPE ('VecRep 'Vec2 'Int64ElemRep) #

Warning: this is only available on LLVM.

data Int8X32# :: TYPE ('VecRep 'Vec32 'Int8ElemRep) #

Warning: this is only available on LLVM.

data Int16X16# :: TYPE ('VecRep 'Vec16 'Int16ElemRep) #

Warning: this is only available on LLVM.

data Int32X8# :: TYPE ('VecRep 'Vec8 'Int32ElemRep) #

Warning: this is only available on LLVM.

data Int64X4# :: TYPE ('VecRep 'Vec4 'Int64ElemRep) #

Warning: this is only available on LLVM.

data Int8X64# :: TYPE ('VecRep 'Vec64 'Int8ElemRep) #

Warning: this is only available on LLVM.

data Int16X32# :: TYPE ('VecRep 'Vec32 'Int16ElemRep) #

Warning: this is only available on LLVM.

data Int32X16# :: TYPE ('VecRep 'Vec16 'Int32ElemRep) #

Warning: this is only available on LLVM.

data Int64X8# :: TYPE ('VecRep 'Vec8 'Int64ElemRep) #

Warning: this is only available on LLVM.

data Word8X16# :: TYPE ('VecRep 'Vec16 'Word8ElemRep) #

Warning: this is only available on LLVM.

data Word16X8# :: TYPE ('VecRep 'Vec8 'Word16ElemRep) #

Warning: this is only available on LLVM.

data Word32X4# :: TYPE ('VecRep 'Vec4 'Word32ElemRep) #

Warning: this is only available on LLVM.

data Word64X2# :: TYPE ('VecRep 'Vec2 'Word64ElemRep) #

Warning: this is only available on LLVM.

data Word8X32# :: TYPE ('VecRep 'Vec32 'Word8ElemRep) #

Warning: this is only available on LLVM.

data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep) #

Warning: this is only available on LLVM.

data Word32X8# :: TYPE ('VecRep 'Vec8 'Word32ElemRep) #

Warning: this is only available on LLVM.

data Word64X4# :: TYPE ('VecRep 'Vec4 'Word64ElemRep) #

Warning: this is only available on LLVM.

data Word8X64# :: TYPE ('VecRep 'Vec64 'Word8ElemRep) #

Warning: this is only available on LLVM.

data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep) #

Warning: this is only available on LLVM.

data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep) #

Warning: this is only available on LLVM.

data Word64X8# :: TYPE ('VecRep 'Vec8 'Word64ElemRep) #

Warning: this is only available on LLVM.

data FloatX4# :: TYPE ('VecRep 'Vec4 'FloatElemRep) #

Warning: this is only available on LLVM.

data DoubleX2# :: TYPE ('VecRep 'Vec2 'DoubleElemRep) #

Warning: this is only available on LLVM.

data FloatX8# :: TYPE ('VecRep 'Vec8 'FloatElemRep) #

Warning: this is only available on LLVM.

data DoubleX4# :: TYPE ('VecRep 'Vec4 'DoubleElemRep) #

Warning: this is only available on LLVM.

data FloatX16# :: TYPE ('VecRep 'Vec16 'FloatElemRep) #

Warning: this is only available on LLVM.

data DoubleX8# :: TYPE ('VecRep 'Vec8 'DoubleElemRep) #

Warning: this is only available on LLVM.

(+#) :: Int# -> Int# -> Int# infixl 6 #

(-#) :: Int# -> Int# -> Int# infixl 6 #

(*#) :: Int# -> Int# -> Int# infixl 7 #

Low word of signed integer multiply.

mulIntMayOflo# :: Int# -> Int# -> Int# #

Return non-zero if there is any possibility that the upper word of a signed integer multiply might contain useful information. Return zero only if you are completely sure that no overflow can occur. On a 32-bit platform, the recommended implementation is to do a 32 x 32 -> 64 signed multiply, and subtract result[63:32] from (result[31] >>signed 31). If this is zero, meaning that the upper word is merely a sign extension of the lower one, no overflow can occur.

On a 64-bit platform it is not always possible to acquire the top 64 bits of the result. Therefore, a recommended implementation is to take the absolute value of both operands, and return 0 iff bits[63:31] of them are zero, since that means that their magnitudes fit within 31 bits, so the magnitude of the product must fit into 62 bits.

If in doubt, return non-zero, but do make an effort to create the correct answer for small args, since otherwise the performance of (*) :: Integer -> Integer -> Integer will be poor.

quotInt# :: Int# -> Int# -> Int# #

Rounds towards zero. The behavior is undefined if the second argument is zero.

Warning: this can fail with an unchecked exception.

remInt# :: Int# -> Int# -> Int# #

Satisfies (quotInt# x y) *# y +# (remInt# x y) == x. The behavior is undefined if the second argument is zero.

Warning: this can fail with an unchecked exception.

quotRemInt# :: Int# -> Int# -> (# Int#, Int# #) #

Rounds towards zero.

Warning: this can fail with an unchecked exception.

andI# :: Int# -> Int# -> Int# #

Bitwise "and".

orI# :: Int# -> Int# -> Int# #

Bitwise "or".

xorI# :: Int# -> Int# -> Int# #

Bitwise "xor".

notI# :: Int# -> Int# #

Bitwise "not", also known as the binary complement.

negateInt# :: Int# -> Int# #

Unary negation. Since the negative Int# range extends one further than the positive range, negateInt# of the most negative number is an identity operation. This way, negateInt# is always its own inverse.

addIntC# :: Int# -> Int# -> (# Int#, Int# #) #

Add signed integers reporting overflow. First member of result is the sum truncated to an Int#; second member is zero if the true sum fits in an Int#, nonzero if overflow occurred (the sum is either too large or too small to fit in an Int#).

subIntC# :: Int# -> Int# -> (# Int#, Int# #) #

Subtract signed integers reporting overflow. First member of result is the difference truncated to an Int#; second member is zero if the true difference fits in an Int#, nonzero if overflow occurred (the difference is either too large or too small to fit in an Int#).

(>#) :: Int# -> Int# -> Int# infix 4 #

(>=#) :: Int# -> Int# -> Int# infix 4 #

(==#) :: Int# -> Int# -> Int# infix 4 #

(/=#) :: Int# -> Int# -> Int# infix 4 #

(<#) :: Int# -> Int# -> Int# infix 4 #

(<=#) :: Int# -> Int# -> Int# infix 4 #

uncheckedIShiftL# :: Int# -> Int# -> Int# #

Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

uncheckedIShiftRA# :: Int# -> Int# -> Int# #

Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

uncheckedIShiftRL# :: Int# -> Int# -> Int# #

Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

quotInt8# :: Int8# -> Int8# -> Int8# #

Warning: this can fail with an unchecked exception.

remInt8# :: Int8# -> Int8# -> Int8# #

Warning: this can fail with an unchecked exception.

quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #) #

Warning: this can fail with an unchecked exception.

quotWord8# :: Word8# -> Word8# -> Word8# #

Warning: this can fail with an unchecked exception.

remWord8# :: Word8# -> Word8# -> Word8# #

Warning: this can fail with an unchecked exception.

quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #) #

Warning: this can fail with an unchecked exception.

quotInt16# :: Int16# -> Int16# -> Int16# #

Warning: this can fail with an unchecked exception.

remInt16# :: Int16# -> Int16# -> Int16# #

Warning: this can fail with an unchecked exception.

quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #) #

Warning: this can fail with an unchecked exception.

quotWord16# :: Word16# -> Word16# -> Word16# #

Warning: this can fail with an unchecked exception.

remWord16# :: Word16# -> Word16# -> Word16# #

Warning: this can fail with an unchecked exception.

quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #) #

Warning: this can fail with an unchecked exception.

addWordC# :: Word# -> Word# -> (# Word#, Int# #) #

Add unsigned integers reporting overflow. The first element of the pair is the result. The second element is the carry flag, which is nonzero on overflow. See also plusWord2#.

subWordC# :: Word# -> Word# -> (# Word#, Int# #) #

Subtract unsigned integers reporting overflow. The first element of the pair is the result. The second element is the carry flag, which is nonzero on overflow.

plusWord2# :: Word# -> Word# -> (# Word#, Word# #) #

Add unsigned integers, with the high part (carry) in the first component of the returned pair and the low part in the second component of the pair. See also addWordC#.

quotWord# :: Word# -> Word# -> Word# #

Warning: this can fail with an unchecked exception.

remWord# :: Word# -> Word# -> Word# #

Warning: this can fail with an unchecked exception.

quotRemWord# :: Word# -> Word# -> (# Word#, Word# #) #

Warning: this can fail with an unchecked exception.

quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #) #

Takes high word of dividend, then low word of dividend, then divisor. Requires that high word < divisor.

Warning: this can fail with an unchecked exception.

or# :: Word# -> Word# -> Word# #

uncheckedShiftL# :: Word# -> Int# -> Word# #

Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

uncheckedShiftRL# :: Word# -> Int# -> Word# #

Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

popCnt8# :: Word# -> Word# #

Count the number of set bits in the lower 8 bits of a word.

popCnt16# :: Word# -> Word# #

Count the number of set bits in the lower 16 bits of a word.

popCnt32# :: Word# -> Word# #

Count the number of set bits in the lower 32 bits of a word.

popCnt64# :: Word# -> Word# #

Count the number of set bits in a 64-bit word.

popCnt# :: Word# -> Word# #

Count the number of set bits in a word.

pdep8# :: Word# -> Word# -> Word# #

Deposit bits to lower 8 bits of a word at locations specified by a mask.

pdep16# :: Word# -> Word# -> Word# #

Deposit bits to lower 16 bits of a word at locations specified by a mask.

pdep32# :: Word# -> Word# -> Word# #

Deposit bits to lower 32 bits of a word at locations specified by a mask.

pdep64# :: Word# -> Word# -> Word# #

Deposit bits to a word at locations specified by a mask.

pdep# :: Word# -> Word# -> Word# #

Deposit bits to a word at locations specified by a mask.

pext8# :: Word# -> Word# -> Word# #

Extract bits from lower 8 bits of a word at locations specified by a mask.

pext16# :: Word# -> Word# -> Word# #

Extract bits from lower 16 bits of a word at locations specified by a mask.

pext32# :: Word# -> Word# -> Word# #

Extract bits from lower 32 bits of a word at locations specified by a mask.

pext64# :: Word# -> Word# -> Word# #

Extract bits from a word at locations specified by a mask.

pext# :: Word# -> Word# -> Word# #

Extract bits from a word at locations specified by a mask.

clz8# :: Word# -> Word# #

Count leading zeros in the lower 8 bits of a word.

clz16# :: Word# -> Word# #

Count leading zeros in the lower 16 bits of a word.

clz32# :: Word# -> Word# #

Count leading zeros in the lower 32 bits of a word.

clz64# :: Word# -> Word# #

Count leading zeros in a 64-bit word.

clz# :: Word# -> Word# #

Count leading zeros in a word.

ctz8# :: Word# -> Word# #

Count trailing zeros in the lower 8 bits of a word.

ctz16# :: Word# -> Word# #

Count trailing zeros in the lower 16 bits of a word.

ctz32# :: Word# -> Word# #

Count trailing zeros in the lower 32 bits of a word.

ctz64# :: Word# -> Word# #

Count trailing zeros in a 64-bit word.

ctz# :: Word# -> Word# #

Count trailing zeros in a word.

byteSwap16# :: Word# -> Word# #

Swap bytes in the lower 16 bits of a word. The higher bytes are undefined.

byteSwap32# :: Word# -> Word# #

Swap bytes in the lower 32 bits of a word. The higher bytes are undefined.

byteSwap64# :: Word# -> Word# #

Swap bytes in a 64 bits of a word.

byteSwap# :: Word# -> Word# #

Swap bytes in a word.

bitReverse8# :: Word# -> Word# #

Reverse the order of the bits in a 8-bit word.

bitReverse16# :: Word# -> Word# #

Reverse the order of the bits in a 16-bit word.

bitReverse32# :: Word# -> Word# #

Reverse the order of the bits in a 32-bit word.

bitReverse64# :: Word# -> Word# #

Reverse the order of the bits in a 64-bit word.

bitReverse# :: Word# -> Word# #

Reverse the order of the bits in a word.

(>##) :: Double# -> Double# -> Int# infix 4 #

(>=##) :: Double# -> Double# -> Int# infix 4 #

(==##) :: Double# -> Double# -> Int# infix 4 #

(/=##) :: Double# -> Double# -> Int# infix 4 #

(<##) :: Double# -> Double# -> Int# infix 4 #

(<=##) :: Double# -> Double# -> Int# infix 4 #

(+##) :: Double# -> Double# -> Double# infixl 6 #

(-##) :: Double# -> Double# -> Double# infixl 6 #

(*##) :: Double# -> Double# -> Double# infixl 7 #

(/##) :: Double# -> Double# -> Double# infixl 7 #

Warning: this can fail with an unchecked exception.

double2Int# :: Double# -> Int# #

Truncates a Double# value to the nearest Int#. Results are undefined if the truncation if truncation yields a value outside the range of Int#.

logDouble# :: Double# -> Double# #

Warning: this can fail with an unchecked exception.

log1pDouble# :: Double# -> Double# #

Warning: this can fail with an unchecked exception.

asinDouble# :: Double# -> Double# #

Warning: this can fail with an unchecked exception.

acosDouble# :: Double# -> Double# #

Warning: this can fail with an unchecked exception.

(**##) :: Double# -> Double# -> Double# #

Exponentiation.

decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #) #

Convert to integer. First component of the result is -1 or 1, indicating the sign of the mantissa. The next two are the high and low 32 bits of the mantissa respectively, and the last is the exponent.

decodeDouble_Int64# :: Double# -> (# Int#, Int# #) #

Decode Double# into mantissa and base-2 exponent.

divideFloat# :: Float# -> Float# -> Float# #

Warning: this can fail with an unchecked exception.

float2Int# :: Float# -> Int# #

Truncates a Float# value to the nearest Int#. Results are undefined if the truncation if truncation yields a value outside the range of Int#.

logFloat# :: Float# -> Float# #

Warning: this can fail with an unchecked exception.

log1pFloat# :: Float# -> Float# #

Warning: this can fail with an unchecked exception.

asinFloat# :: Float# -> Float# #

Warning: this can fail with an unchecked exception.

acosFloat# :: Float# -> Float# #

Warning: this can fail with an unchecked exception.

decodeFloat_Int# :: Float# -> (# Int#, Int# #) #

Convert to integers. First Int# in result is the mantissa; second is the exponent.

newArray# :: Int# -> a -> State# d -> (# State# d, MutableArray# d a #) #

Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.

readArray# :: MutableArray# d a -> Int# -> State# d -> (# State# d, a #) #

Read from specified index of mutable array. Result is not yet evaluated.

Warning: this can fail with an unchecked exception.

writeArray# :: MutableArray# d a -> Int# -> a -> State# d -> State# d #

Write to specified index of mutable array.

Warning: this can fail with an unchecked exception.

sizeofArray# :: Array# a -> Int# #

Return the number of elements in the array.

sizeofMutableArray# :: MutableArray# d a -> Int# #

Return the number of elements in the array.

indexArray# :: Array# a -> Int# -> (# a #) #

Read from the specified index of an immutable array. The result is packaged into an unboxed unary tuple; the result itself is not yet evaluated. Pattern matching on the tuple forces the indexing of the array to happen but does not evaluate the element itself. Evaluating the thunk prevents additional thunks from building up on the heap. Avoiding these thunks, in turn, reduces references to the argument array, allowing it to be garbage collected more promptly.

Warning: this can fail with an unchecked exception.

unsafeFreezeArray# :: MutableArray# d a -> State# d -> (# State# d, Array# a #) #

Make a mutable array immutable, without copying.

unsafeThawArray# :: Array# a -> State# d -> (# State# d, MutableArray# d a #) #

Make an immutable array mutable, without copying.

copyArray# :: Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d #

Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.

Warning: this can fail with an unchecked exception.

copyMutableArray# :: MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d #

Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. In the case where the source and destination are the same array the source and destination regions may overlap.

Warning: this can fail with an unchecked exception.

cloneArray# :: Array# a -> Int# -> Int# -> Array# a #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

cloneMutableArray# :: MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

freezeArray# :: MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #) #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

thawArray# :: Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

casArray# :: MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) #

Given an array, an offset, the expected old value, and the new value, perform an atomic compare and swap (i.e. write the new value if the current value and the old value are the same pointer). Returns 0 if the swap succeeds and 1 if it fails. Additionally, returns the element at the offset after the operation completes. This means that on a success the new value is returned, and on a failure the actual old value (not the expected one) is returned. Implies a full memory barrier. The use of a pointer equality on a lifted value makes this function harder to use correctly than casIntArray#. All of the difficulties of using reallyUnsafePtrEquality# correctly apply to casArray# as well.

newSmallArray# :: Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #) #

Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.

shrinkSmallMutableArray# :: SmallMutableArray# d a -> Int# -> State# d -> State# d #

Shrink mutable array to new specified size, in the specified state thread. The new size argument must be less than or equal to the current size as reported by sizeofSmallMutableArray#.

readSmallArray# :: SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #) #

Read from specified index of mutable array. Result is not yet evaluated.

Warning: this can fail with an unchecked exception.

writeSmallArray# :: SmallMutableArray# d a -> Int# -> a -> State# d -> State# d #

Write to specified index of mutable array.

Warning: this can fail with an unchecked exception.

sizeofSmallArray# :: SmallArray# a -> Int# #

Return the number of elements in the array.

sizeofSmallMutableArray# :: SmallMutableArray# d a -> Int# #

Return the number of elements in the array. Note that this is deprecated as it is unsafe in the presence of resize operations on the same byte array.

getSizeofSmallMutableArray# :: SmallMutableArray# d a -> State# d -> (# State# d, Int# #) #

Return the number of elements in the array.

indexSmallArray# :: SmallArray# a -> Int# -> (# a #) #

Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.

Warning: this can fail with an unchecked exception.

unsafeFreezeSmallArray# :: SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #) #

Make a mutable array immutable, without copying.

unsafeThawSmallArray# :: SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #) #

Make an immutable array mutable, without copying.

copySmallArray# :: SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d #

Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.

Warning: this can fail with an unchecked exception.

copySmallMutableArray# :: SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d #

Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. The source and destination arrays can refer to the same array. Both arrays must fully contain the specified ranges, but this is not checked. The regions are allowed to overlap, although this is only possible when the same array is provided as both the source and the destination.

Warning: this can fail with an unchecked exception.

cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.