const-0: Read-only mutable primitives

Copyright(c) 2019 Edward Kmett
LicenseBSD-2-Clause OR Apache-2.0
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Const.Unsafe

Description

 

Documentation

class (Constable q q, forall a. Coercible (q a) (p a)) => Constable q p | p -> q Source #

Instances
Constable ConstByteArray MutableByteArray Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstByteArray ConstByteArray Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstIORef IORef Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstIORef ConstIORef Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstForeignPtr ForeignPtr Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstForeignPtr ConstForeignPtr Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstPtr Ptr Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstPtr ConstPtr Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstSTRef s :: Type -> Type) (ConstSTRef s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstSTRef s :: Type -> Type) (STRef s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstMutVar s :: Type -> Type) (ConstMutVar s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstMutVar s :: Type -> Type) (MutVar s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (SmallConstArray s :: Type -> Type) (SmallConstArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (SmallConstArray s :: Type -> Type) (SmallMutableArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstPrimArray s :: Type -> Type) (ConstPrimArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstPrimArray s :: Type -> Type) (MutablePrimArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstArray s :: Type -> Type) (ConstArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstArray s :: Type -> Type) (MutableArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

newtype ConstPtr a Source #

Constructors

ConstPtr 

Fields

Instances
DiffTorsor ConstPtr Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

act :: Diff a b -> ConstPtr a -> ConstPtr b

diff :: ConstPtr b -> ConstPtr a -> Diff a b

Eq (ConstPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

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

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

Data a => Data (ConstPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

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

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

toConstr :: ConstPtr a -> Constr #

dataTypeOf :: ConstPtr a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (ConstPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

compare :: ConstPtr a -> ConstPtr a -> Ordering #

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

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

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

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

max :: ConstPtr a -> ConstPtr a -> ConstPtr a #

min :: ConstPtr a -> ConstPtr a -> ConstPtr a #

Show (ConstPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

showsPrec :: Int -> ConstPtr a -> ShowS #

show :: ConstPtr a -> String #

showList :: [ConstPtr a] -> ShowS #

Storable (ConstPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

sizeOf :: ConstPtr a -> Int #

alignment :: ConstPtr a -> Int #

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

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

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

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

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

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

Constable ConstPtr Ptr Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstPtr ConstPtr Source # 
Instance details

Defined in Data.Const.Unsafe

newtype ConstForeignPtr a Source #

Instances
DiffTorsor ConstForeignPtr Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

act :: Diff a b -> ConstForeignPtr a -> ConstForeignPtr b

diff :: ConstForeignPtr b -> ConstForeignPtr a -> Diff a b

Eq (ConstForeignPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Data a => Data (ConstForeignPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

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

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

toConstr :: ConstForeignPtr a -> Constr #

dataTypeOf :: ConstForeignPtr a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (ConstForeignPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Show (ConstForeignPtr a) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstForeignPtr ForeignPtr Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstForeignPtr ConstForeignPtr Source # 
Instance details

Defined in Data.Const.Unsafe

type Unforeign ConstForeignPtr Source # 
Instance details

Defined in Foreign.Const.ForeignPtr

newtype ConstArray s a Source #

Constructors

ConstArray 

Fields

Instances
Constable (ConstArray s :: Type -> Type) (ConstArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstArray s :: Type -> Type) (MutableArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Eq (ConstArray s a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

(==) :: ConstArray s a -> ConstArray s a -> Bool #

(/=) :: ConstArray s a -> ConstArray s a -> Bool #

newtype ConstByteArray s Source #

Constructors

ConstByteArray 

Fields

Instances
Eq (ConstByteArray s) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstByteArray MutableByteArray Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstByteArray ConstByteArray Source # 
Instance details

Defined in Data.Const.Unsafe

newtype ConstPrimArray s a Source #

Constructors

ConstPrimArray 

Fields

Instances
Constable (ConstPrimArray s :: Type -> Type) (ConstPrimArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstPrimArray s :: Type -> Type) (MutablePrimArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Eq (ConstPrimArray s a) Source # 
Instance details

Defined in Data.Const.Unsafe

newtype ConstMutVar s a Source #

Constructors

ConstMutVar 

Fields

Instances
Constable (ConstMutVar s :: Type -> Type) (ConstMutVar s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstMutVar s :: Type -> Type) (MutVar s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Eq (ConstMutVar s a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

(==) :: ConstMutVar s a -> ConstMutVar s a -> Bool #

(/=) :: ConstMutVar s a -> ConstMutVar s a -> Bool #

newtype ConstIORef a Source #

Constructors

ConstIORef 
Instances
Eq (ConstIORef a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

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

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

Constable ConstIORef IORef Source # 
Instance details

Defined in Data.Const.Unsafe

Constable ConstIORef ConstIORef Source # 
Instance details

Defined in Data.Const.Unsafe

newtype ConstSTRef s a Source #

Constructors

ConstSTRef 
Instances
Constable (ConstSTRef s :: Type -> Type) (ConstSTRef s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (ConstSTRef s :: Type -> Type) (STRef s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Eq (ConstSTRef s a) Source # 
Instance details

Defined in Data.Const.Unsafe

Methods

(==) :: ConstSTRef s a -> ConstSTRef s a -> Bool #

(/=) :: ConstSTRef s a -> ConstSTRef s a -> Bool #

newtype SmallConstArray s a Source #

Constructors

SmallConstArray 

Fields

Instances
Constable (SmallConstArray s :: Type -> Type) (SmallConstArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Constable (SmallConstArray s :: Type -> Type) (SmallMutableArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Const.Unsafe

Eq (SmallConstArray s a) Source # 
Instance details

Defined in Data.Const.Unsafe

constant :: forall p a q. Constable q p => p a -> q a Source #

unsafeConstantCoercion :: forall p a q. Constable q p => Coercion (q a) (p a) Source #

unsafePtr :: forall p a. APtr p => p a -> Ptr a Source #

unsafePtrCoercion :: forall p a. APtr p => Coercion (Ptr a) (p a) Source #

unsafeForeignPtr :: forall p a. AForeignPtr p => p a -> ForeignPtr a Source #

unsafeArray :: forall s p a. AnArray s p => p a -> MutableArray s a Source #

unsafeArrayCoercion :: forall s p a. AnArray s p => Coercion (MutableArray s a) (p a) Source #

unsafeByteArray :: forall s p. AByteArray p => p s -> MutableByteArray s Source #

unsafeByteArrayCoercion :: forall p s. AByteArray p => Coercion (MutableByteArray s) (p s) Source #

unsafePrimArray :: forall s p a. APrimArray s p => p a -> MutablePrimArray s a Source #

unsafePrimArrayCoercion :: forall s p a. APrimArray s p => Coercion (MutablePrimArray s a) (p a) Source #

unsafeSmallArray :: forall s p a. ASmallArray s p => p a -> SmallMutableArray s a Source #

unsafeSmallArrayCoercion :: forall s p a. ASmallArray s p => Coercion (SmallMutableArray s a) (p a) Source #

unsafeMutVar :: forall s p a. AMutVar s p => p a -> MutVar s a Source #

unsafeMutVarCoercion :: forall s p a. AMutVar s p => Coercion (MutVar s a) (p a) Source #

unsafeIORef :: forall p a. AnIORef p => p a -> IORef a Source #

unsafeIORefCoercion :: forall p a. AnIORef p => Coercion (IORef a) (p a) Source #

unsafeSTRef :: forall s p a. AnSTRef s p => p a -> STRef s a Source #

unsafeSTRefCoercion :: forall s p a. AnSTRef s p => Coercion (STRef s a) (p a) Source #

type ACString s = (s ~ Unapply s CChar, APtr (Unapply s)) Source #

type ACWString s = (s ~ Unapply s CWchar, APtr (Unapply s)) Source #