Copyright | (c) 2019 Edward Kmett |
---|---|
License | BSD-2-Clause OR Apache-2.0 |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Documentation
class (Constable q q, forall a. Coercible (q a) (p a)) => Constable q p | p -> q Source #
Instances
ConstPtr | |
|
Instances
DiffTorsor ConstPtr Source # | |
Eq (ConstPtr a) Source # | |
Data a => Data (ConstPtr a) Source # | |
Defined in Data.Const.Unsafe 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 # | |
Show (ConstPtr a) Source # | |
Storable (ConstPtr a) Source # | |
Defined in Data.Const.Unsafe | |
Constable ConstPtr Ptr Source # | |
Defined in Data.Const.Unsafe | |
Constable ConstPtr ConstPtr Source # | |
Defined in Data.Const.Unsafe |
newtype ConstForeignPtr a Source #
Instances
newtype ConstArray s a Source #
ConstArray | |
|
Instances
Constable (ConstArray s :: Type -> Type) (ConstArray s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Constable (ConstArray s :: Type -> Type) (MutableArray s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Eq (ConstArray s a) Source # | |
Defined in Data.Const.Unsafe (==) :: ConstArray s a -> ConstArray s a -> Bool # (/=) :: ConstArray s a -> ConstArray s a -> Bool # |
newtype ConstByteArray s Source #
ConstByteArray | |
|
Instances
Eq (ConstByteArray s) Source # | |
Defined in Data.Const.Unsafe (==) :: ConstByteArray s -> ConstByteArray s -> Bool # (/=) :: ConstByteArray s -> ConstByteArray s -> Bool # | |
Constable ConstByteArray MutableByteArray Source # | |
Defined in Data.Const.Unsafe | |
Constable ConstByteArray ConstByteArray Source # | |
Defined in Data.Const.Unsafe |
newtype ConstPrimArray s a Source #
ConstPrimArray | |
|
Instances
Constable (ConstPrimArray s :: Type -> Type) (ConstPrimArray s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Constable (ConstPrimArray s :: Type -> Type) (MutablePrimArray s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Eq (ConstPrimArray s a) Source # | |
Defined in Data.Const.Unsafe (==) :: ConstPrimArray s a -> ConstPrimArray s a -> Bool # (/=) :: ConstPrimArray s a -> ConstPrimArray s a -> Bool # |
newtype ConstMutVar s a Source #
ConstMutVar | |
|
Instances
Constable (ConstMutVar s :: Type -> Type) (ConstMutVar s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Constable (ConstMutVar s :: Type -> Type) (MutVar s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Eq (ConstMutVar s a) Source # | |
Defined in Data.Const.Unsafe (==) :: ConstMutVar s a -> ConstMutVar s a -> Bool # (/=) :: ConstMutVar s a -> ConstMutVar s a -> Bool # |
newtype ConstIORef a Source #
Instances
Eq (ConstIORef a) Source # | |
Defined in Data.Const.Unsafe (==) :: ConstIORef a -> ConstIORef a -> Bool # (/=) :: ConstIORef a -> ConstIORef a -> Bool # | |
Constable ConstIORef IORef Source # | |
Defined in Data.Const.Unsafe | |
Constable ConstIORef ConstIORef Source # | |
Defined in Data.Const.Unsafe |
newtype ConstSTRef s a Source #
ConstSTRef | |
|
Instances
Constable (ConstSTRef s :: Type -> Type) (ConstSTRef s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Constable (ConstSTRef s :: Type -> Type) (STRef s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Eq (ConstSTRef s a) Source # | |
Defined in Data.Const.Unsafe (==) :: ConstSTRef s a -> ConstSTRef s a -> Bool # (/=) :: ConstSTRef s a -> ConstSTRef s a -> Bool # |
newtype SmallConstArray s a Source #
SmallConstArray | |
|
Instances
Constable (SmallConstArray s :: Type -> Type) (SmallConstArray s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Constable (SmallConstArray s :: Type -> Type) (SmallMutableArray s :: Type -> Type) Source # | |
Defined in Data.Const.Unsafe | |
Eq (SmallConstArray s a) Source # | |
Defined in Data.Const.Unsafe (==) :: SmallConstArray s a -> SmallConstArray s a -> Bool # (/=) :: SmallConstArray s a -> SmallConstArray s a -> Bool # |
type ConstCString = ConstPtr CChar Source #
type ConstCStringLen = (ConstCString, Int) Source #
type ConstCWString = ConstPtr CWchar Source #
type ConstCWStringLen = (ConstCWString, Int) Source #
unsafeConstantCoercion :: forall p a q. Constable q p => Coercion (q a) (p a) Source #
type AForeignPtr = Constable ConstForeignPtr Source #
unsafeForeignPtr :: forall p a. AForeignPtr p => p a -> ForeignPtr a Source #
unsafeForeignPtrCoercion :: forall p a. AForeignPtr p => Coercion (ForeignPtr a) (p a) Source #
type AnArray s = Constable (ConstArray s) 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 #
type AByteArray = Constable ConstByteArray Source #
unsafeByteArray :: forall s p. AByteArray p => p s -> MutableByteArray s Source #
unsafeByteArrayCoercion :: forall p s. AByteArray p => Coercion (MutableByteArray s) (p s) Source #
type APrimArray s = Constable (ConstPrimArray 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 #
type ASmallArray s = Constable (SmallConstArray s) 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 #
type AMutVar s = Constable (ConstMutVar s) 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 #
type AnIORef = Constable ConstIORef Source #
unsafeIORef :: forall p a. AnIORef p => p a -> IORef a Source #
type AnSTRef s = Constable (ConstSTRef s) Source #
unsafeSTRef :: forall s p a. AnSTRef s p => p a -> STRef s a Source #