hspkcs11-0.5: Wrapper for PKCS #11 interface

Safe HaskellNone
LanguageHaskell2010

System.Crypto.Pkcs11

Contents

Synopsis

Library

data Library Source #

Represents a PKCS#11 library.

loadLibrary :: String -> IO Library Source #

Load PKCS#11 dynamically linked library from given path

lib <- loadLibrary "/path/to/dll.so"

releaseLibrary :: Library -> IO () Source #

Releases resources used by loaded library

Reading library information

getInfo :: Library -> IO LibraryInfo Source #

Get general information about Cryptoki library

infoCryptokiVersion :: LibraryInfo -> Version Source #

Cryptoki interface version number, for compatibility with future revisions of this interface

infoManufacturerId :: LibraryInfo -> String Source #

ID of the Cryptoki library manufacturer

infoFlags :: LibraryInfo -> Int Source #

bit flags reserved for future versions. Must be zero for this version

infoLibraryVersion :: LibraryInfo -> Version Source #

Cryptoki library version number

Slots

getSlotNum Source #

Arguments

:: Library

Library to be used for operation.

-> Bool

If True will return only slots with tokens in them.

-> IO CULong

Number of slots.

Return number of slots in the system.

getSlotList Source #

Arguments

:: Library

Library to be used for operation.

-> Bool

If True will return only slots with tokens in them.

-> Int

Maximum number of slot IDs to be returned.

-> IO [SlotId] 

Get a list of slot IDs in the system. Can filter for slots with attached tokens.

slotsIds <- getSlotList lib True 10

In this example retrieves list of, at most 10 (third parameter) slot identifiers with tokens present (second parameter is set to True)

Reading slot information

getSlotInfo :: Library -> SlotId -> IO SlotInfo Source #

Obtains information about a particular slot in the system

slotInfo <- getSlotInfo lib slotId

slotInfoFlags :: SlotInfo -> Int Source #

bit flags indicating capabilities and status of the slot as defined in https://www.cryptsoft.com/pkcs11doc/v220/pkcs11__all_8h.html#aCK_SLOT_INFO

Working with tokens

getTokenInfo :: Library -> SlotId -> IO TokenInfo Source #

Obtains information about a particular token in the system

tokenInfo <- getTokenInfo lib slotId

tokenInfoFlags :: TokenInfo -> Int Source #

bit flags indicating capabilities and status of the device as defined in https://www.cryptsoft.com/pkcs11doc/v220/pkcs11__all_8h.html#aCK_TOKEN_INFO

initToken Source #

Arguments

:: Library

PKCS#11 library

-> SlotId

slot id in which to initialize token

-> ByteString

token's security officer password

-> String

new label for the token

-> IO () 

Initialize a token in a given slot. All objects created by user on the token are destroyed.

initPin :: Session -> ByteString -> IO () Source #

Initializes normal user's PIN. Session should be logged in by SO user in other words it should be in RWSOFunctions state.

setPin Source #

Arguments

:: Session

session to act on

-> ByteString

old PIN

-> ByteString

new PIN

-> IO () 

Changes PIN of a currently logged in user.

Mechanisms

getMechanismList :: Library -> SlotId -> Int -> IO [Int] Source #

Obtains a list of mechanism types supported by a token

getMechanismInfo :: Library -> SlotId -> MechType -> IO MechInfo Source #

Obtains information about a particular mechanism possibly supported by a token

data MechInfo Source #

Represent information about a mechanism. Returned by getMechanismInfo function.

mechInfoMinKeySize :: MechInfo -> Int Source #

Minimum size of a key in bits or bytes depending on the mechanism.

mechInfoMaxKeySize :: MechInfo -> Int Source #

Maximum size of a key in bits or bytes depending on the mechanism.

data Mech Source #

Represents mechanism with parameters to be used in cryptographic operation. Parameterless mechanism can be created with simpleMech function. Few example operations using this data structure are encrypt, generateKey.

Instances

Storable Mech Source # 

Methods

sizeOf :: Mech -> Int #

alignment :: Mech -> Int #

peekElemOff :: Ptr Mech -> Int -> IO Mech #

pokeElemOff :: Ptr Mech -> Int -> Mech -> IO () #

peekByteOff :: Ptr b -> Int -> IO Mech #

pokeByteOff :: Ptr b -> Int -> Mech -> IO () #

peek :: Ptr Mech -> IO Mech #

poke :: Ptr Mech -> Mech -> IO () #

simpleMech :: MechType -> Mech Source #

Return parameterless mechanism which can be used in cryptographic operation.

Session management

data Session Source #

Represent session. Created by withSession function.

withSession Source #

Arguments

:: Library

Library to use.

-> SlotId

Slot ID for which to open session.

-> Bool

If True will open writable session, otherwise will open read-only session.

-> (Session -> IO a)

Callback function which is executed while session is open.

-> IO a

Returns a result of callback function.

Opens a read-only or read-write session with a token in a given slot and then closes it after callback function is finished.

login Source #

Arguments

:: Session

session to act on

-> UserType

type of user to login

-> ByteString

user's PIN

-> IO () 

Logs a user into a token.

logout :: Session -> IO () Source #

Logs a user out from a token.

sessionInfoSlotId :: SessionInfo -> SlotId Source #

Slot for which session is open

sessionInfoDeviceError :: SessionInfo -> CULong Source #

Device specific error code.

Object attributes

type ObjectHandle = CULong Source #

Used to reference an object

data Attribute Source #

Represents an attribute of an object

Constructors

Class ClassType

class of an object, e.g. PrivateKey, SecretKey

KeyType KeyTypeValue

e.g. RSA or AES

Label String

object's label

Token Bool

whether object is stored on the token or is a temporary session object

Decrypt Bool

allow/deny encryption function for an object

ModulusBits Int

number of bits used by modulus, for example in RSA public key

Modulus Integer

modulus value, used by RSA keys

PublicExponent Integer

value of public exponent, used by RSA public keys

PrimeBits Int

number of bits used by prime in classic Diffie-Hellman

Prime Integer

value of prime modulus, used in classic Diffie-Hellman

Base Integer

value of generator, used in classic Diffie-Hellman

ValueLen Int

length in bytes of the corresponding Value attribute

Value ByteString

object's value attribute, for example it is a DER encoded certificate for certificate objects

Extractable Bool

allows or denys extraction of certain attributes of private keys

destroyObject :: Session -> ObjectHandle -> IO () Source #

Deletes an object from token or session.

createObject :: Session -> [Attribute] -> IO ObjectHandle Source #

Creates an object from given list of attributes and returns a reference to created object.

copyObject :: Session -> ObjectHandle -> [Attribute] -> IO ObjectHandle Source #

Makes a copy of an object and changes attributes of copied object, returns a reference to new object.

getObjectSize :: Session -> ObjectHandle -> IO CULong Source #

Returns an approximate amount of space occupied by an object in bytes.

Searching objects

findObjects :: Session -> [Attribute] -> IO [ObjectHandle] Source #

Searches current session for objects matching provided attributes list, returns a list of matching object handles

Reading object attributes

Writing attributes

setAttributes :: Session -> ObjectHandle -> [Attribute] -> IO () Source #

Modifies attributes of an object.

Key generation

generateKey :: Session -> Mech -> [Attribute] -> IO ObjectHandle Source #

Generates a symmetric key using provided mechanism and applies provided attributes to resulting key object.

Examples:

Generate 128-bit AES key:

keyHandle <- generateKey sess (simpleMech AesKeyGen) [ValueLen 16]

Generate 1024-bit Diffie-Hellman domain parameters using PKCS#3 mechanism:

dhParamsHandle <- generateKey sess (simpleMech DhPkcsParameterGen) [PrimeBits 1028]

generateKeyPair Source #

Arguments

:: Session

session in which to generate key

-> Mech

a mechanism to use for key generation, for example 'simpleMech RsaPkcs'

-> [Attribute]

attributes applied to generated public key object

-> [Attribute]

attributes applied to generated private key object

-> IO (ObjectHandle, ObjectHandle)

created objects references, first is public key, second is private key

Generates an asymmetric key pair using provided mechanism.

Examples:

Generate an 2048-bit RSA key:

(pubKey, privKey) <- generateKeyPair sess (simpleMech RsaPkcsKeyPairGen) [ModulusBits 2048] []

deriveKey :: Session -> Mech -> ObjectHandle -> [Attribute] -> IO ObjectHandle Source #

Derives a key from a base key using provided mechanism and applies provided attributes to a resulting key. Can be used to derive symmetric key using Diffie-Hellman key exchange.

Key wrapping/unwrapping

wrapKey Source #

Arguments

:: Mech

Mechanism used to wrap key (to encrypt)

-> Session

Session in which both keys reside.

-> ObjectHandle

Key which will be used to wrap (encrypt) another key

-> ObjectHandle

Key to be wrapped

-> CULong

Maximum size in bytes of a resulting byte array

-> IO ByteString

Resulting opaque wrapped key

Wrap a key using provided wrapping key and return opaque byte array representing wrapped key. This byte array can be stored in user application and can be used later to recreate wrapped key using unwrapKey function.

Example wrapping AES key using RSA public key:

wrappedAesKey <- wrapKey (simpleMech RsaPkcs) sess pubRsaKeyHandle aesKeyHandle 300

unwrapKey Source #

Arguments

:: Mech

Mechanism to use for unwrapping (decryption).

-> Session

Session in which to perform operation.

-> ObjectHandle

Handle to a key which will be used to unwrap (decrypt) key.

-> ByteString

Key to be unwrapped.

-> [Attribute]

Attributes applied to unwrapped key object.

-> IO ObjectHandle

Unwrapped key handle.

Unwrap a key from opaque byte string and apply attributes to a resulting key object.

Example unwrapping AES key using RSA private key:

unwrappedAesKey <- unwrapKey (simpleMech RsaPkcs) sess privRsaKeyHandle wrappedAesKey [Class SecretKey, KeyType AES]

Encryption/decryption

decrypt Source #

Arguments

:: Mech

Mechanism used for decryption.

-> Session

Session on which key resides.

-> ObjectHandle

Key handle used for decryption.

-> ByteString

Encrypted data to be decrypted.

-> CULong

Maximum number of bytes to be returned.

-> IO ByteString

Decrypted data

Decrypt data using provided mechanism and key handle.

Example AES ECB decryption.

decData <- decrypt (simpleMech AesEcb) sess aesKeyHandle encData 1000

encrypt Source #

Arguments

:: Mech

Mechanism to use for encryption.

-> Session

Session in which to perform operation.

-> ObjectHandle

Key handle.

-> ByteString

Data to be encrypted.

-> CULong

Maximum number of bytes to be returned.

-> IO ByteString

Encrypted data.

Encrypt data using provided mechanism and key handle.

Multipart operations

decryptInit :: Mech -> Session -> ObjectHandle -> IO () Source #

Initialize a multi-part decryption operation using provided mechanism and key.

encryptInit Source #

Arguments

:: Mech

Mechanism to use for encryption.

-> Session

Session in which to perform operation.

-> ObjectHandle

Key handle.

-> IO () 

Initialize multi-part encryption operation.

Digest

digest Source #

Arguments

:: Mech

Digest mechanism.

-> Session

Session to be used for digesting.

-> ByteString

Data to be digested.

-> CULong

Maximum number of bytes to be returned.

-> IO ByteString

Resulting digest.

Calculates digest aka hash of a data using provided mechanism.

Example calculating SHA256 hash:

>>> digest (simpleMech Sha256) sess (replicate 16 0) 1000
"7G\b\255\247q\157\213\151\158\200u\213l\210(om<\247\236\&1z;%c*\171(\236\&7\187"

Signing

sign Source #

Arguments

:: Mech

Mechanism to use for signing.

-> Session

Session to work in.

-> ObjectHandle

Key handle.

-> ByteString

Data to be signed.

-> CULong

Maximum number of bytes to be returned.

-> IO ByteString

Signature.

Signs data using provided mechanism and key.

Example signing with RSA PKCS#1

signature <- sign (simpleMech RsaPkcs) sess privKeyHandle signedData 1000

verify Source #

Arguments

:: Mech

Mechanism to be used for signature validation.

-> Session

Session to be used.

-> ObjectHandle

Key handle.

-> ByteString

Signed data.

-> ByteString

Signature.

-> IO Bool

True is signature is valid, False otherwise.

Verifies signature using provided mechanism and key.

Example signature verification using RSA public key:

>>> verify (simpleMech RsaPkcs) sess pubKeyHandle signedData signature
True

Random

seedRandom :: Session -> ByteString -> IO () Source #

Mixes provided seed data with token's seed

generateRandom Source #

Arguments

:: Session

Session to work on.

-> CULong

Number of bytes to generate.

-> IO ByteString

Generated random bytes.

Generates random data using token's RNG.