{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE DeriveGeneric #-} {-| Module : Text.YAML.Config Description : Reads and parses config file Copyright : (c) Philip Woods 2015 License : AGPL-3 Maintainer : elzairthesorcerer@gmail.com Stability : experimental Portabiltity : Linux -} module Text.YAML.Config ( readConfig ) where import Control.Applicative ((<$>)) import qualified Data.ByteString as BS import Data.Info (ProjectInfo(..), HostInfo(..), confPath) import Data.Text (Text) import Data.Yaml (FromJSON(..), ToJSON(..), decodeEither) import GHC.Generics (Generic) data MyConfig = MyConfig { version :: Text, -- ^ Version number providers :: [ProviderConfig] -- ^ List of providers } deriving (Show, Generic) instance FromJSON MyConfig instance ToJSON MyConfig data ProviderConfig = ProviderConfig { provider_name :: Text, -- ^ Name of Provider (i.e. bitbucket) repositories :: [RepositoryConfig] -- ^ List of repositories } deriving (Show, Generic) instance FromJSON ProviderConfig instance ToJSON ProviderConfig data RepositoryConfig = RepositoryConfig { repository_name :: Text, -- ^ Name of repositories branches :: [BranchConfig] -- ^ List of branches } deriving (Show, Generic) instance FromJSON RepositoryConfig instance ToJSON RepositoryConfig data BranchConfig = BranchConfig { branch_name :: Text, -- ^ Name of branch pre_commands :: Maybe [Text], -- ^ List of commands to execute before building container hosts :: Maybe [HostConfig] -- ^ List of application hosts } deriving (Show, Generic) instance FromJSON BranchConfig instance ToJSON BranchConfig data HostConfig = HostConfig { host_name :: Text, -- ^ Name of host (i.e. example.com) run_options :: Maybe Text -- ^ Options to pass to Docker } deriving (Show, Generic) instance FromJSON HostConfig instance ToJSON HostConfig -- | Parse the /providers/ section of the config file parseConfig :: [ProviderConfig] -- ^ The list of providers -> [ProjectInfo] -- ^ The list of projects parseConfig ps = concat $ map parseProvider ps where parseProvider p = concatMap (parseRepo p) (repositories p) parseRepo p r = concatMap (parseBranch p r) (branches r) parseBranch p r b = [ProjectInfo{provider = provider_name p, repository = repository_name r, branch = branch_name b, preCommands = pre_commands b, hostInfo = parseHosts $ hosts b}] parseHosts Nothing = Nothing parseHosts (Just []) = Just [] parseHosts (Just (h:hs)) = (HostInfo{hostName = host_name h, runOptions = run_options h} :) <$> parseHosts (Just hs) -- | Return either the parsed contents of the config file or an error readConfig :: IO (Either String [ProjectInfo]) -- ^ Success: List of information on various projects; -- Failure: Error readConfig = do contents <- decodeEither <$> BS.readFile confPath :: IO (Either String MyConfig) case contents of Left err -> return $ Left err Right myconf -> return $ Right $ parseConfig $ providers myconf