solidabis-koodihaaste/src/Data/Config.hs

39 lines
1.1 KiB
Haskell

{-# LANGUAGE DeriveGeneric #-}
{-|
Module : Config
Description : Config types
Copyright : (c) Mats Rauhala, 2019
License : BSD3
Maintainer : mats.rauhala@iki.fi
Stability : experimental
Portability : POSIX
The config type with a helper function for reading the config from disk
-}
module Data.Config where
import Server (Port)
import Solidabis.API (Token)
import Control.Monad.Trans (MonadIO, liftIO)
import Data.Aeson (FromJSON)
import Data.Yaml.Config
import GHC.Generics (Generic)
import Servant.Client (BaseUrl)
-- | Config type
--
-- These are all values that should be known statically beforehand
data Config
= Config { _accessToken :: Token
, _solidabisBase :: BaseUrl
, _port :: Port
, _training :: FilePath }
deriving (Show, Generic)
instance FromJSON Config
-- | Read the configuration yaml from file
readConfigFromFile :: MonadIO m => FilePath -> m Config
readConfigFromFile path = liftIO $ loadYamlSettings [path] [] ignoreEnv