File: Types.hs

package info (click to toggle)
haskell-cryptonite 0.20-5
  • links: PTS, VCS
  • area: main
  • in suites: stretch
  • size: 2,936 kB
  • ctags: 1,963
  • sloc: ansic: 31,728; haskell: 10,183; makefile: 3
file content (100 lines) | stat: -rw-r--r-- 3,331 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
-- |
-- Module      : Crypto.Error.Types
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : stable
-- Portability : Good
--
-- Cryptographic Error enumeration and handling
--
{-# LANGUAGE DeriveDataTypeable #-}
module Crypto.Error.Types
    ( CryptoError(..)
    , CryptoFailable(..)
    , throwCryptoErrorIO
    , throwCryptoError
    , onCryptoFailure
    , eitherCryptoError
    , maybeCryptoError
    ) where

import qualified Control.Exception as E
import           Data.Data

import           Crypto.Internal.Imports

-- | Enumeration of all possible errors that can be found in this library
data CryptoError =
    -- symmetric cipher errors
      CryptoError_KeySizeInvalid
    | CryptoError_IvSizeInvalid
    | CryptoError_AEADModeNotSupported
    -- public key cryptography error
    | CryptoError_SecretKeySizeInvalid
    | CryptoError_SecretKeyStructureInvalid
    | CryptoError_PublicKeySizeInvalid
    | CryptoError_SharedSecretSizeInvalid
    -- Message authentification error
    | CryptoError_MacKeyInvalid
    | CryptoError_AuthenticationTagSizeInvalid
    deriving (Show,Eq,Enum,Data,Typeable)

instance E.Exception CryptoError

-- | A simple Either like type to represent a computation that can fail
--
-- 2 possibles values are:
--
-- * 'CryptoPassed' : The computation succeeded, and contains the result of the computation
--
-- * 'CryptoFailed' : The computation failed, and contains the cryptographic error associated
--
data CryptoFailable a =
      CryptoPassed a
    | CryptoFailed CryptoError
    deriving (Show)

instance Eq a => Eq (CryptoFailable a) where
    (==) (CryptoPassed a)  (CryptoPassed b)  = a == b
    (==) (CryptoFailed e1) (CryptoFailed e2) = e1 == e2
    (==) _                 _                 = False

instance Functor CryptoFailable where
    fmap f (CryptoPassed a) = CryptoPassed (f a)
    fmap _ (CryptoFailed r) = CryptoFailed r

instance Applicative CryptoFailable where
    pure a     = CryptoPassed a
    (<*>) fm m = fm >>= \p -> m >>= \r2 -> return (p r2)
instance Monad CryptoFailable where
    return a = CryptoPassed a
    (>>=) m1 m2 = do
        case m1 of
            CryptoPassed a -> m2 a
            CryptoFailed e -> CryptoFailed e

-- | Throw an CryptoError as exception on CryptoFailed result,
-- otherwise return the computed value
throwCryptoErrorIO :: CryptoFailable a -> IO a
throwCryptoErrorIO (CryptoFailed e) = E.throwIO e
throwCryptoErrorIO (CryptoPassed r) = return r

-- | Same as 'throwCryptoErrorIO' but throw the error asynchronously.
throwCryptoError :: CryptoFailable a -> a
throwCryptoError (CryptoFailed e) = E.throw e
throwCryptoError (CryptoPassed r) = r

-- | Simple 'either' like combinator for CryptoFailable type
onCryptoFailure :: (CryptoError -> r) -> (a -> r) -> CryptoFailable a -> r
onCryptoFailure onError _         (CryptoFailed e) = onError e
onCryptoFailure _       onSuccess (CryptoPassed r) = onSuccess r

-- | Transform a CryptoFailable to an Either
eitherCryptoError :: CryptoFailable a -> Either CryptoError a
eitherCryptoError (CryptoFailed e) = Left e
eitherCryptoError (CryptoPassed a) = Right a

-- | Transform a CryptoFailable to a Maybe
maybeCryptoError :: CryptoFailable a -> Maybe a
maybeCryptoError (CryptoFailed _) = Nothing
maybeCryptoError (CryptoPassed r) = Just r