| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Crypto.Pkcs11
Documentation
_serialSession :: Int Source #
type ObjectHandle = CULong Source #
type SessionHandle = CULong Source #
type FunctionListPtr = Ptr () Source #
type SlotInfoPtr = Ptr SlotInfo Source #
type TokenInfoPtr = Ptr TokenInfo Source #
type LlAttributePtr = Ptr LlAttribute Source #
type MechInfoPtr = Ptr MechInfo Source #
type GetFunctionListFun = Ptr FunctionListPtr -> IO CULong Source #
Constructors
| Version | |
Fields
| |
Constructors
| Info | |
Fields | |
Constructors
| SlotInfo | |
Constructors
| TokenInfo | |
Fields | |
Constructors
| MechInfo | |
Fields | |
Constructors
| Mech | |
Fields
| |
initialize :: FunctionListPtr -> IO Rv Source #
getSlotInfo' :: FunctionListPtr -> Int -> IO (Rv, SlotInfo) Source #
getTokenInfo' :: FunctionListPtr -> Int -> IO (Rv, TokenInfo) Source #
closeSession' :: FunctionListPtr -> CULong -> IO Rv Source #
findObjectsFinal' :: FunctionListPtr -> CULong -> IO Rv Source #
Constructors
| SecurityOfficer | |
| User | |
| ContextSpecific |
_login :: FunctionListPtr -> SessionHandle -> UserType -> ByteString -> IO Rv Source #
_generateKeyPair :: FunctionListPtr -> SessionHandle -> Int -> [Attribute] -> [Attribute] -> IO (Rv, ObjectHandle, ObjectHandle) Source #
_getMechanismList :: FunctionListPtr -> Int -> Int -> IO (Rv, [CULong]) Source #
_getMechanismInfo :: FunctionListPtr -> Int -> Int -> IO (Rv, MechInfo) Source #
data KeyTypeValue Source #
Instances
data AttributeType Source #
Constructors
| ClassType | |
| TokenType | |
| LabelType | |
| KeyTypeType | |
| DecryptType | |
| ModulusType | |
| ModulusBitsType | |
| PublicExponentType | |
| PrivateExponentType | |
| Prime1Type | |
| Prime2Type | |
| Exponent1Type | |
| Exponent2Type | |
| CoefficientType |
Instances
data LlAttribute Source #
Constructors
| LlAttribute | |
Fields
| |
Instances
_attrType :: Attribute -> AttributeType Source #
_valueSize :: Attribute -> Int Source #
_valuesSize :: [Attribute] -> Int Source #
_makeLowLevelAttrs :: [Attribute] -> Ptr () -> [LlAttribute] Source #
_withAttribs :: [Attribute] -> (Ptr LlAttribute -> IO a) -> IO a Source #
_llAttrToAttr :: LlAttribute -> IO Attribute Source #
Constructors
| Library | |
Fields | |
Constructors
| Session SessionHandle FunctionListPtr |
releaseLibrary :: Library -> IO () Source #
_closeSessionEx :: Session -> IO () Source #
_findObjectsEx :: Session -> IO [ObjectHandle] Source #
_findObjectsFinalEx :: Session -> IO () Source #
findObjects :: Session -> [Attribute] -> IO [ObjectHandle] Source #
generateKeyPair :: Session -> Int -> [Attribute] -> [Attribute] -> IO (ObjectHandle, ObjectHandle) Source #
getObjectAttr :: Session -> ObjectHandle -> AttributeType -> IO Attribute Source #
getModulus :: Session -> ObjectHandle -> IO Integer Source #
getPublicExponent :: Session -> ObjectHandle -> IO Integer Source #
Constructors
| RsaPkcsKeyPairGen | |
| RsaPkcs | |
| AesEcb | |
| AesCbc | |
| AesMac | |
| AesMacGeneral | |
| AesCbcPad | |
| AesCtr |
_decryptInit :: MechType -> Session -> ObjectHandle -> IO () Source #
decrypt :: MechType -> Session -> ObjectHandle -> ByteString -> IO ByteString Source #
_encryptInit :: MechType -> Session -> ObjectHandle -> IO () Source #
encrypt :: MechType -> Session -> ObjectHandle -> ByteString -> IO ByteString Source #
unwrapKey :: MechType -> Session -> ObjectHandle -> ByteString -> [Attribute] -> IO ObjectHandle Source #
cK_FUNCTION_LISTc_GetSlotList :: FunPtr (CUChar -> Ptr CULong -> Ptr CULong -> IO CULong) -> CUChar -> Ptr CULong -> Ptr CULong -> IO CULong Source #
getSlotInfo''_ :: FunPtr (CULong -> SlotInfoPtr -> IO CULong) -> CULong -> SlotInfoPtr -> IO CULong Source #
getTokenInfo''_ :: FunPtr (CULong -> TokenInfoPtr -> IO CULong) -> CULong -> TokenInfoPtr -> IO CULong Source #
cK_FUNCTION_LISTc_OpenSession :: FunPtr (CULong -> CULong -> Ptr () -> FunPtr (CULong -> CULong -> Ptr () -> IO CULong) -> Ptr CULong -> IO CULong) -> CULong -> CULong -> Ptr () -> FunPtr (CULong -> CULong -> Ptr () -> IO CULong) -> Ptr CULong -> IO CULong Source #
cK_FUNCTION_LISTc_FindObjectsInit :: FunPtr (CULong -> LlAttributePtr -> CULong -> IO CULong) -> CULong -> LlAttributePtr -> CULong -> IO CULong Source #
cK_FUNCTION_LISTc_FindObjects :: FunPtr (CULong -> Ptr CULong -> CULong -> Ptr CULong -> IO CULong) -> CULong -> Ptr CULong -> CULong -> Ptr CULong -> IO CULong Source #
cK_FUNCTION_LISTc_Login :: FunPtr (CULong -> CULong -> Ptr CUChar -> CULong -> IO CULong) -> CULong -> CULong -> Ptr CUChar -> CULong -> IO CULong Source #
cK_FUNCTION_LISTc_GenerateKeyPair :: FunPtr (CULong -> MechPtr -> LlAttributePtr -> CULong -> LlAttributePtr -> CULong -> Ptr CULong -> Ptr CULong -> IO CULong) -> CULong -> MechPtr -> LlAttributePtr -> CULong -> LlAttributePtr -> CULong -> Ptr CULong -> Ptr CULong -> IO CULong Source #
cK_FUNCTION_LISTc_GetMechanismList :: FunPtr (CULong -> Ptr CULong -> Ptr CULong -> IO CULong) -> CULong -> Ptr CULong -> Ptr CULong -> IO CULong Source #
_getMechanismInfo'_ :: FunPtr (CULong -> CULong -> MechInfoPtr -> IO CULong) -> CULong -> CULong -> MechInfoPtr -> IO CULong Source #
cK_FUNCTION_LISTc_GetAttributeValue :: FunPtr (CULong -> CULong -> LlAttributePtr -> CULong -> IO CULong) -> CULong -> CULong -> LlAttributePtr -> CULong -> IO CULong Source #
cK_FUNCTION_LISTc_DecryptInit :: FunPtr (CULong -> MechPtr -> CULong -> IO CULong) -> CULong -> MechPtr -> CULong -> IO CULong Source #
cK_FUNCTION_LISTc_Decrypt :: FunPtr (CULong -> Ptr CUChar -> CULong -> Ptr CUChar -> Ptr CULong -> IO CULong) -> CULong -> Ptr CUChar -> CULong -> Ptr CUChar -> Ptr CULong -> IO CULong Source #
cK_FUNCTION_LISTc_EncryptInit :: FunPtr (CULong -> MechPtr -> CULong -> IO CULong) -> CULong -> MechPtr -> CULong -> IO CULong Source #