File: PKey.hsc

package info (click to toggle)
haskell-hsopenssl 0.11.7.8-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 556 kB
  • sloc: haskell: 1,562; ansic: 451; makefile: 16
file content (237 lines) | stat: -rw-r--r-- 7,862 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
{-# LANGUAGE DeriveDataTypeable        #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ForeignFunctionInterface  #-}
{-# LANGUAGE CApiFFI                   #-}
{-# LANGUAGE Rank2Types                #-}
{-# OPTIONS_GHC -fno-warn-orphans      #-}
-- |An interface to asymmetric cipher keypair.
module OpenSSL.EVP.PKey
    ( PublicKey(..)
    , KeyPair(..)
    , SomePublicKey
    , SomeKeyPair
    )
    where
#include "HsOpenSSL.h"
import Data.Typeable
import Data.Maybe
import Foreign
import Foreign.C
import OpenSSL.DSA
import OpenSSL.EVP.Digest
import OpenSSL.EVP.Internal
import OpenSSL.RSA
import OpenSSL.Utils

-- |Instances of this class has at least public portion of a
-- keypair. They might or might not have the private key.
class (Eq k, Typeable k, PKey k) => PublicKey k where

    -- |Wrap an arbitrary public key into polymorphic type
    -- 'SomePublicKey'.
    fromPublicKey :: k -> SomePublicKey
    fromPublicKey = SomePublicKey

    -- |Cast from the polymorphic type 'SomePublicKey' to the concrete
    -- type. Return 'Nothing' if failed.
    toPublicKey :: SomePublicKey -> Maybe k
    toPublicKey (SomePublicKey pk) = cast pk

-- |Instances of this class has both of public and private portions of
-- a keypair.
class PublicKey a => KeyPair a where

    -- |Wrap an arbitrary keypair into polymorphic type 'SomeKeyPair'.
    fromKeyPair :: a -> SomeKeyPair
    fromKeyPair = SomeKeyPair

    -- |Cast from the polymorphic type 'SomeKeyPair' to the concrete
    -- type. Return 'Nothing' if failed.
    toKeyPair :: SomeKeyPair -> Maybe a
    toKeyPair (SomeKeyPair pk) = cast pk



#if OPENSSL_VERSION_PREREQ(3,0)
foreign import capi unsafe "openssl/evp.h EVP_PKEY_get_base_id" getType :: Ptr EVP_PKEY -> IO CInt
#elif OPENSSL_VERSION_NUMBER >= 0x10100000L
foreign import capi unsafe "openssl/evp.h EVP_PKEY_base_id" getType :: Ptr EVP_PKEY -> IO CInt
#else
getType :: Ptr EVP_PKEY -> IO CInt
getType = (#peek EVP_PKEY, type)
#endif

-- Reconstruct the concrete public-key type from an EVP_PKEY.
withConcretePubKey :: VaguePKey -> (forall k. PublicKey k => k -> IO a) -> IO a
withConcretePubKey pk f
    = withPKeyPtr pk $ \ pkeyPtr ->
          do pkeyType <- getType pkeyPtr
             case pkeyType of
#if !defined(OPENSSL_NO_RSA)
               (#const EVP_PKEY_RSA)
                   -> do rsaPtr   <- _get1_RSA pkeyPtr
                         Just rsa <- absorbRSAPtr rsaPtr
                         f (rsa :: RSAPubKey)
#endif
#if !defined(OPENSSL_NO_DSA)
               (#const EVP_PKEY_DSA)
                   -> do dsaPtr   <- _get1_DSA pkeyPtr
                         Just dsa <- absorbDSAPtr dsaPtr
                         f (dsa :: DSAPubKey)
#endif
               _   -> fail ("withConcretePubKey: unsupported EVP_PKEY type: " ++ show pkeyType)

-- Reconstruct the concrete keypair type from an EVP_PKEY.
withConcreteKeyPair :: VaguePKey -> (forall k. KeyPair k => k -> IO a) -> IO a
withConcreteKeyPair pk f
    = withPKeyPtr pk $ \ pkeyPtr ->
          do pkeyType <- getType pkeyPtr
             case pkeyType of
#if !defined(OPENSSL_NO_RSA)
               (#const EVP_PKEY_RSA)
                   -> do rsaPtr   <- _get1_RSA pkeyPtr
                         Just rsa <- absorbRSAPtr rsaPtr
                         f (rsa :: RSAKeyPair)
#endif
#if !defined(OPENSSL_NO_DSA)
               (#const EVP_PKEY_DSA)
                   -> do dsaPtr   <- _get1_DSA pkeyPtr
                         Just dsa <- absorbDSAPtr dsaPtr
                         f (dsa :: DSAKeyPair)
#endif
               _   -> fail ("withConcreteKeyPair: unsupported EVP_PKEY type: " ++ show pkeyType)


-- |This is an opaque type to hold an arbitrary public key in it. The
-- actual key type can be safelly type-casted using 'toPublicKey'.
data SomePublicKey = forall k. PublicKey k => SomePublicKey !k
    deriving Typeable

instance Eq SomePublicKey where
    (SomePublicKey a) == (SomePublicKey b)
        = case cast b of
            Just c  -> a == c
            Nothing -> False  -- different types

instance PublicKey SomePublicKey where
    fromPublicKey = id
    toPublicKey   = Just

instance PKey SomePublicKey where
    toPKey        (SomePublicKey k) = toPKey k
    pkeySize      (SomePublicKey k) = pkeySize k
    pkeyDefaultMD (SomePublicKey k) = pkeyDefaultMD k
    fromPKey pk
        = withConcretePubKey pk (return . Just . SomePublicKey)


-- |This is an opaque type to hold an arbitrary keypair in it. The
-- actual key type can be safelly type-casted using 'toKeyPair'.
data SomeKeyPair = forall k. KeyPair k => SomeKeyPair !k
    deriving Typeable

instance Eq SomeKeyPair where
    (SomeKeyPair a) == (SomeKeyPair b)
        = case cast b of
            Just c  -> a == c
            Nothing -> False

instance PublicKey SomeKeyPair where
    -- Cast the keypair to a public key, hiding its private part.
    fromPublicKey (SomeKeyPair k)
        = SomePublicKey k

    -- It's impossible to cast a public key to a keypair.
    toPublicKey _ = Nothing

instance KeyPair SomeKeyPair where
    fromKeyPair = id
    toKeyPair   = Just

instance PKey SomeKeyPair where
    toPKey        (SomeKeyPair k) = toPKey k
    pkeySize      (SomeKeyPair k) = pkeySize k
    pkeyDefaultMD (SomeKeyPair k) = pkeyDefaultMD k
    fromPKey pk
        = withConcreteKeyPair pk (return . Just . SomeKeyPair)


#if !defined(OPENSSL_NO_RSA)
-- The resulting Ptr RSA must be freed by caller.
foreign import capi unsafe "openssl/evp.h EVP_PKEY_get1_RSA"
        _get1_RSA :: Ptr EVP_PKEY -> IO (Ptr RSA)

foreign import capi unsafe "openssl/evp.h EVP_PKEY_set1_RSA"
        _set1_RSA :: Ptr EVP_PKEY -> Ptr RSA -> IO CInt


rsaToPKey :: RSAKey k => k -> IO VaguePKey
rsaToPKey rsa
    = withRSAPtr rsa $ \rsaPtr ->
        createPKey $ \pkeyPtr ->
          _set1_RSA pkeyPtr rsaPtr >>= failIf_ (/= 1)

rsaFromPKey :: RSAKey k => VaguePKey -> IO (Maybe k)
rsaFromPKey pk
        = withPKeyPtr pk $ \ pkeyPtr ->
          do pkeyType <- getType pkeyPtr
             case pkeyType of
               (#const EVP_PKEY_RSA)
                   -> _get1_RSA pkeyPtr >>= absorbRSAPtr
               _   -> return Nothing

instance PublicKey RSAPubKey
instance PKey RSAPubKey where
    toPKey          = rsaToPKey
    fromPKey        = rsaFromPKey
    pkeySize        = rsaSize
    pkeyDefaultMD _ = return . fromJust =<< getDigestByName "sha1"

instance KeyPair RSAKeyPair
instance PublicKey RSAKeyPair
instance PKey RSAKeyPair where
    toPKey          = rsaToPKey
    fromPKey        = rsaFromPKey
    pkeySize        = rsaSize
    pkeyDefaultMD _ = return . fromJust =<< getDigestByName "sha1"
#endif


#if !defined(OPENSSL_NO_DSA)
foreign import capi unsafe "openssl/evp.h EVP_PKEY_get1_DSA"
        _get1_DSA :: Ptr EVP_PKEY -> IO (Ptr DSA)

foreign import capi unsafe "openssl/evp.h EVP_PKEY_set1_DSA"
        _set1_DSA :: Ptr EVP_PKEY -> Ptr DSA -> IO CInt

dsaToPKey :: DSAKey k => k -> IO VaguePKey
dsaToPKey dsa
    = withDSAPtr dsa $ \dsaPtr ->
        createPKey $ \pkeyPtr ->
          _set1_DSA pkeyPtr dsaPtr >>= failIf_ (/= 1)


dsaFromPKey :: DSAKey k => VaguePKey -> IO (Maybe k)
dsaFromPKey pk
        = withPKeyPtr pk $ \ pkeyPtr ->
          do pkeyType <- getType pkeyPtr
             case pkeyType of
               (#const EVP_PKEY_DSA)
                   -> _get1_DSA pkeyPtr >>= absorbDSAPtr
               _   -> return Nothing

instance PublicKey DSAPubKey
instance PKey DSAPubKey where
    toPKey          = dsaToPKey
    fromPKey        = dsaFromPKey
    pkeySize        = dsaSize
    pkeyDefaultMD _ = return . fromJust =<< getDigestByName "dss1"

instance KeyPair DSAKeyPair
instance PublicKey DSAKeyPair
instance PKey DSAKeyPair where
    toPKey          = dsaToPKey
    fromPKey        = dsaFromPKey
    pkeySize        = dsaSize
    pkeyDefaultMD _ = return . fromJust =<< getDigestByName "dss1"
#endif