-- |
--  Module      : Cfg.Options
--  Copyright   : © Jonathan Lorimer, 2023
--  License     : MIT
--  Maintainer  : jonathanlorimer@pm.me
--  Stability   : stable
--
-- @since 0.0.2.0
--
-- This module contains the options types that we pass to our generic
-- functions. Mostly these are used for registering text transformations on
-- keys, but another interesting use case is choosing between the type
-- constructor and the data constructor for deriving a name for root keys.
module Cfg.Options
  ( -- * Option Types
    KeyOptions (..)
  , RootKey (..)
  , RootOptions (..)
  , ConfigOptions (..)

    -- * Helper Functions
  , defaultKeyOptions
  , defaultRootOptions
  , defaultConfigOptions
  , keyModifier
  )
where

import Data.Text (Text)

-- | Options that pertain to record field accessors.
--
-- @since 0.0.1.0
data KeyOptions = KeyOptions
  { KeyOptions -> Text -> Text
keyOptionsModifier :: Text -> Text
  }

-- | Default key options, does no transformation to record field accessors.
--
-- @since 0.0.2.0
defaultKeyOptions :: KeyOptions
defaultKeyOptions :: KeyOptions
defaultKeyOptions = (Text -> Text) -> KeyOptions
KeyOptions Text -> Text
forall a. a -> a
id

-- | Type that represents a decision between using the type constructor name or
-- the data constructor name as the root key.
--
-- This type is polymorphic so that we can use it to contain a term level text
-- transformation for root keys, as well as be used at the type level
-- parameterized by a type that defines the key modifiers to use.
--
-- @since 0.0.2.0
data RootKey a = ConstructorName a | TypeName a

-- | Options for manipulating a root key
--
-- @since 0.0.2.0
data RootOptions = RootOptions
  { RootOptions -> RootKey (Text -> Text)
rootOptionsRootKey :: RootKey (Text -> Text)
  , RootOptions -> Text -> Text
rootOptionsModifier :: Text -> Text
  }

-- | Default root key option, uses the type constructor name for the root key
-- and applies no transformations to the root key or keys derived from record
-- fields.
--
-- @since 0.0.2.0
defaultRootOptions :: RootOptions
defaultRootOptions :: RootOptions
defaultRootOptions = RootKey (Text -> Text) -> (Text -> Text) -> RootOptions
RootOptions ((Text -> Text) -> RootKey (Text -> Text)
forall a. a -> RootKey a
TypeName Text -> Text
forall a. a -> a
id) Text -> Text
forall a. a -> a
id

-- | Represents all possible kinds of configuration options.
--
-- @since 0.0.2.0
data ConfigOptions = Root RootOptions | Key KeyOptions

-- | Defaults to regular 'KeyOptions' (not 'RootOptions')
--
-- @since 0.0.2.0
defaultConfigOptions :: ConfigOptions
defaultConfigOptions :: ConfigOptions
defaultConfigOptions = KeyOptions -> ConfigOptions
Key KeyOptions
defaultKeyOptions

-- | Helper function that allows us to generically extract the record field
-- modifiers from either a 'RootOptions' or a 'KeyOptions' record.
--
-- @since 0.0.2.0
keyModifier :: ConfigOptions -> (Text -> Text)
keyModifier :: ConfigOptions -> Text -> Text
keyModifier (Root RootOptions
options) = RootOptions -> Text -> Text
rootOptionsModifier RootOptions
options
keyModifier (Key KeyOptions
options) = KeyOptions -> Text -> Text
keyOptionsModifier KeyOptions
options