{-# LANGUAGE DataKinds #-}
{-# LANGUAGE EmptyDataDeriving #-}
module Auth.Biscuit
(
newSecret
, toPublic
, SecretKey
, PublicKey
, serializeSecretKeyHex
, serializePublicKeyHex
, parseSecretKeyHex
, parsePublicKeyHex
, serializeSecretKey
, serializePublicKey
, parseSecretKey
, parsePublicKey
, mkBiscuit
, mkBiscuitWith
, block
, blockContext
, Biscuit
, OpenOrSealed
, Open
, Sealed
, Verified
, Unverified
, BiscuitProof
, Block
, parseB64
, parse
, parseWith
, parseBiscuitUnverified
, checkBiscuitSignatures
, BiscuitEncoding (..)
, ParserConfig (..)
, fromRevocationList
, serializeB64
, serialize
, fromHex
, addBlock
, seal
, fromOpen
, fromSealed
, asOpen
, asSealed
, authorizer
, Authorizer
, authorizeBiscuit
, authorizeBiscuitWithLimits
, Limits (..)
, defaultLimits
, ParseError (..)
, ExecutionError (..)
, AuthorizationSuccess (..)
, MatchedQuery (..)
, query
, queryAuthorizerFacts
, getBindings
, getVariableValues
, getSingleVariableValue
, ToTerm (..)
, FromValue (..)
, Term
, Term' (..)
, getRevocationIds
, getVerifiedBiscuitPublicKey
) where
import Control.Monad ((<=<))
import Control.Monad.Identity (runIdentity)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as Hex
import qualified Data.ByteString.Base64.URL as B64
import Data.Foldable (toList)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Text (Text)
import Auth.Biscuit.Crypto (PublicKey, SecretKey,
convert,
generateSecretKey,
maybeCryptoError,
publicKey, secretKey,
toPublic)
import Auth.Biscuit.Datalog.AST (Authorizer, Block,
FromValue (..), Term,
Term' (..), ToTerm (..),
bContext)
import Auth.Biscuit.Datalog.Executor (ExecutionError (..),
Limits (..),
MatchedQuery (..),
defaultLimits)
import Auth.Biscuit.Datalog.Parser (authorizer, block, query)
import Auth.Biscuit.Datalog.ScopedExecutor (AuthorizationSuccess (..),
getBindings,
getSingleVariableValue,
getVariableValues,
queryAuthorizerFacts)
import Auth.Biscuit.Token (Biscuit,
BiscuitEncoding (..),
BiscuitProof (..), Open,
OpenOrSealed,
ParseError (..),
ParserConfig (..), Sealed,
Unverified, Verified,
addBlock, asOpen,
asSealed,
authorizeBiscuit,
authorizeBiscuitWithLimits,
checkBiscuitSignatures,
fromOpen, fromSealed,
getRevocationIds,
getVerifiedBiscuitPublicKey,
mkBiscuit, mkBiscuitWith,
parseBiscuitUnverified,
parseBiscuitWith, seal,
serializeBiscuit)
blockContext :: Text -> Block
blockContext :: Text -> Block
blockContext Text
c = Block
forall a. Monoid a => a
mempty { bContext :: Maybe Text
bContext = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
c }
fromHex :: MonadFail m => ByteString -> m ByteString
fromHex :: ByteString -> m ByteString
fromHex = (String -> m ByteString)
-> (ByteString -> m ByteString)
-> Either String ByteString
-> m ByteString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> m ByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String ByteString -> m ByteString)
-> (ByteString -> Either String ByteString)
-> ByteString
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
Hex.decode
newSecret :: IO SecretKey
newSecret :: IO SecretKey
newSecret = IO SecretKey
forall (m :: * -> *). MonadRandom m => m SecretKey
generateSecretKey
serializeSecretKey :: SecretKey -> ByteString
serializeSecretKey :: SecretKey -> ByteString
serializeSecretKey = SecretKey -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert
serializePublicKey :: PublicKey -> ByteString
serializePublicKey :: PublicKey -> ByteString
serializePublicKey = PublicKey -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert
serializeSecretKeyHex :: SecretKey -> ByteString
serializeSecretKeyHex :: SecretKey -> ByteString
serializeSecretKeyHex = ByteString -> ByteString
Hex.encode (ByteString -> ByteString)
-> (SecretKey -> ByteString) -> SecretKey -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SecretKey -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert
serializePublicKeyHex :: PublicKey -> ByteString
serializePublicKeyHex :: PublicKey -> ByteString
serializePublicKeyHex = ByteString -> ByteString
Hex.encode (ByteString -> ByteString)
-> (PublicKey -> ByteString) -> PublicKey -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PublicKey -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert
parseSecretKey :: ByteString -> Maybe SecretKey
parseSecretKey :: ByteString -> Maybe SecretKey
parseSecretKey = CryptoFailable SecretKey -> Maybe SecretKey
forall a. CryptoFailable a -> Maybe a
maybeCryptoError (CryptoFailable SecretKey -> Maybe SecretKey)
-> (ByteString -> CryptoFailable SecretKey)
-> ByteString
-> Maybe SecretKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> CryptoFailable SecretKey
forall ba. ByteArrayAccess ba => ba -> CryptoFailable SecretKey
secretKey
parseSecretKeyHex :: ByteString -> Maybe SecretKey
parseSecretKeyHex :: ByteString -> Maybe SecretKey
parseSecretKeyHex = ByteString -> Maybe SecretKey
parseSecretKey (ByteString -> Maybe SecretKey)
-> (ByteString -> Maybe ByteString)
-> ByteString
-> Maybe SecretKey
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ByteString -> Maybe ByteString
forall (m :: * -> *). MonadFail m => ByteString -> m ByteString
fromHex
parsePublicKey :: ByteString -> Maybe PublicKey
parsePublicKey :: ByteString -> Maybe PublicKey
parsePublicKey = CryptoFailable PublicKey -> Maybe PublicKey
forall a. CryptoFailable a -> Maybe a
maybeCryptoError (CryptoFailable PublicKey -> Maybe PublicKey)
-> (ByteString -> CryptoFailable PublicKey)
-> ByteString
-> Maybe PublicKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> CryptoFailable PublicKey
forall ba. ByteArrayAccess ba => ba -> CryptoFailable PublicKey
publicKey
parsePublicKeyHex :: ByteString -> Maybe PublicKey
parsePublicKeyHex :: ByteString -> Maybe PublicKey
parsePublicKeyHex = ByteString -> Maybe PublicKey
parsePublicKey (ByteString -> Maybe PublicKey)
-> (ByteString -> Maybe ByteString)
-> ByteString
-> Maybe PublicKey
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ByteString -> Maybe ByteString
forall (m :: * -> *). MonadFail m => ByteString -> m ByteString
fromHex
parse :: PublicKey -> ByteString -> Either ParseError (Biscuit OpenOrSealed Verified)
parse :: PublicKey
-> ByteString -> Either ParseError (Biscuit OpenOrSealed Verified)
parse PublicKey
pk = Identity (Either ParseError (Biscuit OpenOrSealed Verified))
-> Either ParseError (Biscuit OpenOrSealed Verified)
forall a. Identity a -> a
runIdentity (Identity (Either ParseError (Biscuit OpenOrSealed Verified))
-> Either ParseError (Biscuit OpenOrSealed Verified))
-> (ByteString
-> Identity (Either ParseError (Biscuit OpenOrSealed Verified)))
-> ByteString
-> Either ParseError (Biscuit OpenOrSealed Verified)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserConfig Identity
-> ByteString
-> Identity (Either ParseError (Biscuit OpenOrSealed Verified))
forall (m :: * -> *).
Applicative m =>
ParserConfig m
-> ByteString
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
parseBiscuitWith ParserConfig :: forall (m :: * -> *).
BiscuitEncoding
-> (Set ByteString -> m Bool)
-> (Maybe Int -> PublicKey)
-> ParserConfig m
ParserConfig
{ encoding :: BiscuitEncoding
encoding = BiscuitEncoding
RawBytes
, isRevoked :: Set ByteString -> Identity Bool
isRevoked = Identity Bool -> Set ByteString -> Identity Bool
forall a b. a -> b -> a
const (Identity Bool -> Set ByteString -> Identity Bool)
-> Identity Bool -> Set ByteString -> Identity Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Identity Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
, getPublicKey :: Maybe Int -> PublicKey
getPublicKey = PublicKey -> Maybe Int -> PublicKey
forall (f :: * -> *) a. Applicative f => a -> f a
pure PublicKey
pk
}
parseB64 :: PublicKey -> ByteString -> Either ParseError (Biscuit OpenOrSealed Verified)
parseB64 :: PublicKey
-> ByteString -> Either ParseError (Biscuit OpenOrSealed Verified)
parseB64 PublicKey
pk = Identity (Either ParseError (Biscuit OpenOrSealed Verified))
-> Either ParseError (Biscuit OpenOrSealed Verified)
forall a. Identity a -> a
runIdentity (Identity (Either ParseError (Biscuit OpenOrSealed Verified))
-> Either ParseError (Biscuit OpenOrSealed Verified))
-> (ByteString
-> Identity (Either ParseError (Biscuit OpenOrSealed Verified)))
-> ByteString
-> Either ParseError (Biscuit OpenOrSealed Verified)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserConfig Identity
-> ByteString
-> Identity (Either ParseError (Biscuit OpenOrSealed Verified))
forall (m :: * -> *).
Applicative m =>
ParserConfig m
-> ByteString
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
parseBiscuitWith ParserConfig :: forall (m :: * -> *).
BiscuitEncoding
-> (Set ByteString -> m Bool)
-> (Maybe Int -> PublicKey)
-> ParserConfig m
ParserConfig
{ encoding :: BiscuitEncoding
encoding = BiscuitEncoding
UrlBase64
, isRevoked :: Set ByteString -> Identity Bool
isRevoked = Identity Bool -> Set ByteString -> Identity Bool
forall a b. a -> b -> a
const (Identity Bool -> Set ByteString -> Identity Bool)
-> Identity Bool -> Set ByteString -> Identity Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Identity Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
, getPublicKey :: Maybe Int -> PublicKey
getPublicKey = PublicKey -> Maybe Int -> PublicKey
forall (f :: * -> *) a. Applicative f => a -> f a
pure PublicKey
pk
}
parseWith :: Applicative m
=> ParserConfig m
-> ByteString
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
parseWith :: ParserConfig m
-> ByteString
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
parseWith = ParserConfig m
-> ByteString
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
forall (m :: * -> *).
Applicative m =>
ParserConfig m
-> ByteString
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
parseBiscuitWith
fromRevocationList :: (Applicative m, Foldable t)
=> t ByteString
-> Set ByteString
-> m Bool
fromRevocationList :: t ByteString -> Set ByteString -> m Bool
fromRevocationList t ByteString
revokedIds Set ByteString
tokenIds =
Bool -> m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> m Bool)
-> (Set ByteString -> Bool) -> Set ByteString -> m Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
not (Bool -> Bool)
-> (Set ByteString -> Bool) -> Set ByteString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set ByteString -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Set ByteString -> m Bool) -> Set ByteString -> m Bool
forall a b. (a -> b) -> a -> b
$ Set ByteString -> Set ByteString -> Set ByteString
forall a. Ord a => Set a -> Set a -> Set a
Set.intersection ([ByteString] -> Set ByteString
forall a. Ord a => [a] -> Set a
Set.fromList ([ByteString] -> Set ByteString) -> [ByteString] -> Set ByteString
forall a b. (a -> b) -> a -> b
$ t ByteString -> [ByteString]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList t ByteString
revokedIds) Set ByteString
tokenIds
serialize :: BiscuitProof p => Biscuit p Verified -> ByteString
serialize :: Biscuit p Verified -> ByteString
serialize = Biscuit p Verified -> ByteString
forall p. BiscuitProof p => Biscuit p Verified -> ByteString
serializeBiscuit
serializeB64 :: BiscuitProof p => Biscuit p Verified -> ByteString
serializeB64 :: Biscuit p Verified -> ByteString
serializeB64 = ByteString -> ByteString
B64.encodeBase64' (ByteString -> ByteString)
-> (Biscuit p Verified -> ByteString)
-> Biscuit p Verified
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Biscuit p Verified -> ByteString
forall p. BiscuitProof p => Biscuit p Verified -> ByteString
serialize