module Network.Hawk.Internal.Server.Types where
import Data.ByteString (ByteString)
import Data.Text (Text)
import Data.Time.Clock.POSIX (POSIXTime)
import Network.HTTP.Types.Method (Method)
import GHC.Generics
import Data.Default
import Network.Hawk.Types
type AuthResult t = AuthResult' (AuthSuccess t)
type AuthResult' r = Either AuthFail r
data AuthFail = AuthFailBadRequest String (Maybe HeaderArtifacts)
| AuthFailUnauthorized String (Maybe Credentials) (Maybe HeaderArtifacts)
| AuthFailStaleTimeStamp String POSIXTime Credentials HeaderArtifacts
deriving (Show, Eq)
data AuthSuccess t = AuthSuccess Credentials HeaderArtifacts t
instance Show t => Show (AuthSuccess t) where
show (AuthSuccess c a t) = "AuthSuccess " ++ show t
instance Eq t => Eq (AuthSuccess t) where
AuthSuccess c a t == AuthSuccess d b u = c == d && a == b && t == u
authValue :: AuthSuccess t -> t
authValue (AuthSuccess _ _ t) = t
authFailMessage :: AuthFail -> String
authFailMessage (AuthFailBadRequest e _) = e
authFailMessage (AuthFailUnauthorized e _ _) = e
authFailMessage (AuthFailStaleTimeStamp e _ _ _) = e
data HawkReq = HawkReq
{ hrqMethod :: Method
, hrqUrl :: ByteString
, hrqHost :: ByteString
, hrqPort :: Maybe Int
, hrqAuthorization :: ByteString
, hrqPayload :: Maybe PayloadInfo
, hrqBewit :: Maybe ByteString
, hrqBewitlessUrl :: ByteString
} deriving Show
instance Default HawkReq where
def = HawkReq "GET" "/" "localhost" Nothing "" Nothing Nothing ""
data Credentials = Credentials
{ scKey :: Key
, scAlgorithm :: HawkAlgo
} deriving (Show, Eq, Generic)
type CredentialsFunc m t = ClientId -> m (Either String (Credentials, t))
type NonceFunc = Key -> POSIXTime -> Nonce -> IO Bool
type Nonce = ByteString