{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Crypto.JOSE.Error
(
Error(..)
, AsError(..)
, InvalidNumberOfParts(..), expectedParts, actualParts
, CompactTextError(..)
, CompactDecodeError(..)
, _CompactInvalidNumberOfParts
, _CompactInvalidText
) where
import Data.Semigroup ((<>))
import Numeric.Natural
import Control.Monad.Trans (MonadTrans(..))
import qualified Crypto.PubKey.RSA as RSA
import Crypto.Error (CryptoError)
import Crypto.Random (MonadRandom(..))
import Control.Lens (Getter, to)
import Control.Lens.TH (makeClassyPrisms, makePrisms)
import qualified Data.Text as T
import qualified Data.Text.Encoding.Error as T
data InvalidNumberOfParts =
InvalidNumberOfParts Natural Natural
deriving (InvalidNumberOfParts -> InvalidNumberOfParts -> Bool
(InvalidNumberOfParts -> InvalidNumberOfParts -> Bool)
-> (InvalidNumberOfParts -> InvalidNumberOfParts -> Bool)
-> Eq InvalidNumberOfParts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InvalidNumberOfParts -> InvalidNumberOfParts -> Bool
$c/= :: InvalidNumberOfParts -> InvalidNumberOfParts -> Bool
== :: InvalidNumberOfParts -> InvalidNumberOfParts -> Bool
$c== :: InvalidNumberOfParts -> InvalidNumberOfParts -> Bool
Eq)
instance Show InvalidNumberOfParts where
show :: InvalidNumberOfParts -> String
show (InvalidNumberOfParts Natural
n Natural
m) =
String
"Expected " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Natural -> String
forall a. Show a => a -> String
show Natural
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" parts; got " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Natural -> String
forall a. Show a => a -> String
show Natural
m
expectedParts, actualParts :: Getter InvalidNumberOfParts Natural
expectedParts :: (Natural -> f Natural)
-> InvalidNumberOfParts -> f InvalidNumberOfParts
expectedParts = (InvalidNumberOfParts -> Natural)
-> (Natural -> f Natural)
-> InvalidNumberOfParts
-> f InvalidNumberOfParts
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((InvalidNumberOfParts -> Natural)
-> (Natural -> f Natural)
-> InvalidNumberOfParts
-> f InvalidNumberOfParts)
-> (InvalidNumberOfParts -> Natural)
-> (Natural -> f Natural)
-> InvalidNumberOfParts
-> f InvalidNumberOfParts
forall a b. (a -> b) -> a -> b
$ \(InvalidNumberOfParts Natural
n Natural
_) -> Natural
n
actualParts :: (Natural -> f Natural)
-> InvalidNumberOfParts -> f InvalidNumberOfParts
actualParts = (InvalidNumberOfParts -> Natural)
-> (Natural -> f Natural)
-> InvalidNumberOfParts
-> f InvalidNumberOfParts
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((InvalidNumberOfParts -> Natural)
-> (Natural -> f Natural)
-> InvalidNumberOfParts
-> f InvalidNumberOfParts)
-> (InvalidNumberOfParts -> Natural)
-> (Natural -> f Natural)
-> InvalidNumberOfParts
-> f InvalidNumberOfParts
forall a b. (a -> b) -> a -> b
$ \(InvalidNumberOfParts Natural
_ Natural
n) -> Natural
n
data CompactTextError = CompactTextError
Natural
T.UnicodeException
deriving (CompactTextError -> CompactTextError -> Bool
(CompactTextError -> CompactTextError -> Bool)
-> (CompactTextError -> CompactTextError -> Bool)
-> Eq CompactTextError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompactTextError -> CompactTextError -> Bool
$c/= :: CompactTextError -> CompactTextError -> Bool
== :: CompactTextError -> CompactTextError -> Bool
$c== :: CompactTextError -> CompactTextError -> Bool
Eq)
instance Show CompactTextError where
show :: CompactTextError -> String
show (CompactTextError Natural
n UnicodeException
s) =
String
"Invalid text at part " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Natural -> String
forall a. Show a => a -> String
show Natural
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
": " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> UnicodeException -> String
forall a. Show a => a -> String
show UnicodeException
s
data CompactDecodeError
= CompactInvalidNumberOfParts InvalidNumberOfParts
| CompactInvalidText CompactTextError
deriving (CompactDecodeError -> CompactDecodeError -> Bool
(CompactDecodeError -> CompactDecodeError -> Bool)
-> (CompactDecodeError -> CompactDecodeError -> Bool)
-> Eq CompactDecodeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompactDecodeError -> CompactDecodeError -> Bool
$c/= :: CompactDecodeError -> CompactDecodeError -> Bool
== :: CompactDecodeError -> CompactDecodeError -> Bool
$c== :: CompactDecodeError -> CompactDecodeError -> Bool
Eq)
makePrisms ''CompactDecodeError
instance Show CompactDecodeError where
show :: CompactDecodeError -> String
show (CompactInvalidNumberOfParts InvalidNumberOfParts
e) = String
"Invalid number of parts: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> InvalidNumberOfParts -> String
forall a. Show a => a -> String
show InvalidNumberOfParts
e
show (CompactInvalidText CompactTextError
e) = String
"Invalid text: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> CompactTextError -> String
forall a. Show a => a -> String
show CompactTextError
e
data Error
= AlgorithmNotImplemented
| AlgorithmMismatch String
| KeyMismatch T.Text
| KeySizeTooSmall
| OtherPrimesNotSupported
| RSAError RSA.Error
| CryptoError CryptoError
| CompactDecodeError CompactDecodeError
| JSONDecodeError String
| NoUsableKeys
| JWSCritUnprotected
| JWSNoValidSignatures
| JWSInvalidSignature
| JWSNoSignatures
deriving (Error -> Error -> Bool
(Error -> Error -> Bool) -> (Error -> Error -> Bool) -> Eq Error
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Error -> Error -> Bool
$c/= :: Error -> Error -> Bool
== :: Error -> Error -> Bool
$c== :: Error -> Error -> Bool
Eq, Int -> Error -> ShowS
[Error] -> ShowS
Error -> String
(Int -> Error -> ShowS)
-> (Error -> String) -> ([Error] -> ShowS) -> Show Error
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Error] -> ShowS
$cshowList :: [Error] -> ShowS
show :: Error -> String
$cshow :: Error -> String
showsPrec :: Int -> Error -> ShowS
$cshowsPrec :: Int -> Error -> ShowS
Show)
makeClassyPrisms ''Error
instance (
MonadRandom m
, MonadTrans t
, Functor (t m)
, Monad (t m)
) => MonadRandom (t m) where
getRandomBytes :: Int -> t m byteArray
getRandomBytes = m byteArray -> t m byteArray
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m byteArray -> t m byteArray)
-> (Int -> m byteArray) -> Int -> t m byteArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> m byteArray
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes