{-# LANGUAGE OverloadedStrings #-} {- | Module : $Header$ Description : Author : Nils 'bash0r' Jonsson Copyright : (c) 2015 Nils 'bash0r' Jonsson License : MIT Maintainer : aka.bash0r@gmail.com Stability : unstable Portability : non-portable (Portability is untested.) The 'Configuration' module contains all relevant information -} module Headergen.Configuration ( Configuration (..) , createDictionary ) where import Control.Applicative import Control.Monad import Data.Aeson import Headergen.Template -- | The configuration is used to read / write configuration to JSON. data Configuration = Configuration { getModule :: String , getDescription :: String , getAuthor :: String , getCopyright :: String , getLicense :: String , getMaintainer :: String , getStability :: String , getPortability :: String } deriving (Show, Eq) instance ToJSON Configuration where toJSON (Configuration mod desc auth copyr lic maint stab portab) = object [ "module" .= mod , "author" .= auth , "description" .= desc , "copyright" .= copyr , "license" .= lic , "maintainer" .= maint , "stability" .= stab , "portability" .= portab ] instance FromJSON Configuration where parseJSON (Object o) = Configuration <$> o .: "module" <*> o .: "description" <*> o .: "author" <*> o .: "copyright" <*> o .: "license" <*> o .: "maintainer" <*> o .: "stability" <*> o .: "portability" parseJSON _ = empty createDictionary :: Configuration -> Dictionary createDictionary (Configuration mod des aut cop lic mai sta por) = [ ("module" , mod) , ("description", des) , ("author" , aut) , ("copyright" , cop) , ("license" , lic) , ("maintainer" , mai) , ("stability" , sta) , ("portability", por) ]