summaryrefslogtreecommitdiff
path: root/cryptonite-backport/Crypto/Error
diff options
context:
space:
mode:
Diffstat (limited to 'cryptonite-backport/Crypto/Error')
-rw-r--r--cryptonite-backport/Crypto/Error/Types.hs106
1 files changed, 106 insertions, 0 deletions
diff --git a/cryptonite-backport/Crypto/Error/Types.hs b/cryptonite-backport/Crypto/Error/Types.hs
new file mode 100644
index 00000000..4aaf4e04
--- /dev/null
+++ b/cryptonite-backport/Crypto/Error/Types.hs
@@ -0,0 +1,106 @@
1-- |
2-- Module : Crypto.Error.Types
3-- License : BSD-style
4-- Maintainer : Vincent Hanquez <vincent@snarc.org>
5-- Stability : stable
6-- Portability : Good
7--
8-- Cryptographic Error enumeration and handling
9--
10{-# LANGUAGE DeriveDataTypeable #-}
11module Crypto.Error.Types
12 ( CryptoError(..)
13 , CryptoFailable(..)
14 , throwCryptoErrorIO
15 , throwCryptoError
16 , onCryptoFailure
17 , eitherCryptoError
18 , maybeCryptoError
19 ) where
20
21import qualified Control.Exception as E
22import Data.Data
23
24import Crypto.Internal.Imports
25
26-- | Enumeration of all possible errors that can be found in this library
27data CryptoError =
28 -- symmetric cipher errors
29 CryptoError_KeySizeInvalid
30 | CryptoError_IvSizeInvalid
31 | CryptoError_AEADModeNotSupported
32 -- public key cryptography error
33 | CryptoError_SecretKeySizeInvalid
34 | CryptoError_SecretKeyStructureInvalid
35 | CryptoError_PublicKeySizeInvalid
36 | CryptoError_SharedSecretSizeInvalid
37 -- elliptic cryptography error
38 | CryptoError_EcScalarOutOfBounds
39 | CryptoError_PointSizeInvalid
40 | CryptoError_PointFormatInvalid
41 | CryptoError_PointFormatUnsupported
42 | CryptoError_PointCoordinatesInvalid
43 -- Message authentification error
44 | CryptoError_MacKeyInvalid
45 | CryptoError_AuthenticationTagSizeInvalid
46 deriving (Show,Eq,Enum,Data,Typeable)
47
48instance E.Exception CryptoError
49
50-- | A simple Either like type to represent a computation that can fail
51--
52-- 2 possibles values are:
53--
54-- * 'CryptoPassed' : The computation succeeded, and contains the result of the computation
55--
56-- * 'CryptoFailed' : The computation failed, and contains the cryptographic error associated
57--
58data CryptoFailable a =
59 CryptoPassed a
60 | CryptoFailed CryptoError
61 deriving (Show)
62
63instance Eq a => Eq (CryptoFailable a) where
64 (==) (CryptoPassed a) (CryptoPassed b) = a == b
65 (==) (CryptoFailed e1) (CryptoFailed e2) = e1 == e2
66 (==) _ _ = False
67
68instance Functor CryptoFailable where
69 fmap f (CryptoPassed a) = CryptoPassed (f a)
70 fmap _ (CryptoFailed r) = CryptoFailed r
71
72instance Applicative CryptoFailable where
73 pure a = CryptoPassed a
74 (<*>) fm m = fm >>= \p -> m >>= \r2 -> return (p r2)
75instance Monad CryptoFailable where
76 return a = CryptoPassed a
77 (>>=) m1 m2 = do
78 case m1 of
79 CryptoPassed a -> m2 a
80 CryptoFailed e -> CryptoFailed e
81
82-- | Throw an CryptoError as exception on CryptoFailed result,
83-- otherwise return the computed value
84throwCryptoErrorIO :: CryptoFailable a -> IO a
85throwCryptoErrorIO (CryptoFailed e) = E.throwIO e
86throwCryptoErrorIO (CryptoPassed r) = return r
87
88-- | Same as 'throwCryptoErrorIO' but throw the error asynchronously.
89throwCryptoError :: CryptoFailable a -> a
90throwCryptoError (CryptoFailed e) = E.throw e
91throwCryptoError (CryptoPassed r) = r
92
93-- | Simple 'either' like combinator for CryptoFailable type
94onCryptoFailure :: (CryptoError -> r) -> (a -> r) -> CryptoFailable a -> r
95onCryptoFailure onError _ (CryptoFailed e) = onError e
96onCryptoFailure _ onSuccess (CryptoPassed r) = onSuccess r
97
98-- | Transform a CryptoFailable to an Either
99eitherCryptoError :: CryptoFailable a -> Either CryptoError a
100eitherCryptoError (CryptoFailed e) = Left e
101eitherCryptoError (CryptoPassed a) = Right a
102
103-- | Transform a CryptoFailable to a Maybe
104maybeCryptoError :: CryptoFailable a -> Maybe a
105maybeCryptoError (CryptoFailed _) = Nothing
106maybeCryptoError (CryptoPassed r) = Just r