{-# LANGUAGE AllowAmbiguousTypes #-}
module IHP.Job.Dashboard.Auth (
AuthenticationMethod(..),
NoAuth(..),
BasicAuth(..),
BasicAuthStatic(..),
) where
import IHP.Prelude
import GHC.TypeLits
import IHP.ControllerPrelude
import System.Environment (lookupEnv)
class AuthenticationMethod a where
authenticate :: (?context :: ControllerContext, ?modelContext :: ModelContext) => IO ()
data NoAuth
data BasicAuth (userEnv :: Symbol) (passEnv :: Symbol)
data BasicAuthStatic (user :: Symbol) (pass :: Symbol)
instance AuthenticationMethod NoAuth where
authenticate :: (?context::ControllerContext, ?modelContext::ModelContext) => IO ()
authenticate = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
instance (KnownSymbol userEnv, KnownSymbol passEnv) => AuthenticationMethod (BasicAuth userEnv passEnv) where
authenticate :: (?context::ControllerContext, ?modelContext::ModelContext) => IO ()
authenticate = do
(Maybe String, Maybe String)
creds <- (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
lookupEnv (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @userEnv) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> IO (Maybe String)
lookupEnv (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @passEnv)
case (Maybe String, Maybe String)
creds of
(Just String
user, Just String
pass) -> (?context::ControllerContext) => Text -> Text -> Text -> IO ()
basicAuth (forall a b. ConvertibleStrings a b => a -> b
cs String
user) (forall a b. ConvertibleStrings a b => a -> b
cs String
pass) Text
"jobs"
(Maybe String, Maybe String)
_ -> forall a. Text -> a
error Text
"Did not find HTTP Basic Auth credentials for Jobs Dashboard."
instance (KnownSymbol user, KnownSymbol pass) => AuthenticationMethod (BasicAuthStatic user pass) where
authenticate :: (?context::ControllerContext, ?modelContext::ModelContext) => IO ()
authenticate = (?context::ControllerContext) => Text -> Text -> Text -> IO ()
basicAuth (forall a b. ConvertibleStrings a b => a -> b
cs forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @user) (forall a b. ConvertibleStrings a b => a -> b
cs forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @pass) Text
"jobs"