{-# language NoFieldSelectors #-}

-- | Description: Config data type for the effect 'Polysemy.Account.Accounts'.
module Polysemy.Account.Data.AccountsConfig where

import Polysemy.Account.Data.Privilege (Privilege)

-- | The configuration for the interpreter for 'Polysemy.Account.Accounts'.
--
-- The defaults, when using 'Privilege', are:
--
-- - Length 20
-- - Don't activate accounts right away
-- - 'Polysemy.Account.Web' privileges
data AccountsConfig p =
  AccountsConfig {
    -- | Length of generated passwords.
    forall p. AccountsConfig p -> Word
passwordLength :: Word,
    -- | Whether new accounts should immediately be marked as active rather than pending, allowing login.
    forall p. AccountsConfig p -> Bool
initActive :: Bool,
    -- | The privileges assigned to a new account.
    forall p. AccountsConfig p -> p
defaultPrivileges :: p
  }
  deriving stock (AccountsConfig p -> AccountsConfig p -> Bool
forall p. Eq p => AccountsConfig p -> AccountsConfig p -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountsConfig p -> AccountsConfig p -> Bool
$c/= :: forall p. Eq p => AccountsConfig p -> AccountsConfig p -> Bool
== :: AccountsConfig p -> AccountsConfig p -> Bool
$c== :: forall p. Eq p => AccountsConfig p -> AccountsConfig p -> Bool
Eq, Int -> AccountsConfig p -> ShowS
forall p. Show p => Int -> AccountsConfig p -> ShowS
forall p. Show p => [AccountsConfig p] -> ShowS
forall p. Show p => AccountsConfig p -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountsConfig p] -> ShowS
$cshowList :: forall p. Show p => [AccountsConfig p] -> ShowS
show :: AccountsConfig p -> String
$cshow :: forall p. Show p => AccountsConfig p -> String
showsPrec :: Int -> AccountsConfig p -> ShowS
$cshowsPrec :: forall p. Show p => Int -> AccountsConfig p -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall p x. Rep (AccountsConfig p) x -> AccountsConfig p
forall p x. AccountsConfig p -> Rep (AccountsConfig p) x
$cto :: forall p x. Rep (AccountsConfig p) x -> AccountsConfig p
$cfrom :: forall p x. AccountsConfig p -> Rep (AccountsConfig p) x
Generic)

json ''AccountsConfig

-- | Convenience alias for using the default privilege type with 'AccountsConfig'.
type AccountsConfigP = AccountsConfig [Privilege]

instance Default p => Default (AccountsConfig p) where
  def :: AccountsConfig p
def = AccountsConfig {
    $sel:passwordLength:AccountsConfig :: Word
passwordLength = Word
20,
    $sel:initActive:AccountsConfig :: Bool
initActive = Bool
False,
    $sel:defaultPrivileges:AccountsConfig :: p
defaultPrivileges = forall a. Default a => a
def
  }