{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Filter.Pyplot.Configuration (
configuration
, inclusionKeys
, directoryKey
, captionKey
, dpiKey
, includePathKey
, saveFormatKey
) where
import Data.Maybe (fromMaybe)
import Data.Default.Class (def)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Yaml
import Data.Yaml.Config (loadYamlSettings, ignoreEnv)
import Text.Pandoc.Filter.Pyplot.Types
directoryKey, captionKey, dpiKey, includePathKey, saveFormatKey :: String
directoryKey = "directory"
captionKey = "caption"
dpiKey = "dpi"
includePathKey = "include"
saveFormatKey = "format"
inclusionKeys :: [String]
inclusionKeys = [ directoryKey
, captionKey
, dpiKey
, includePathKey
, saveFormatKey
]
data ConfigPrecursor
= ConfigPrecursor
{ defaultDirectory_ :: FilePath
, defaultIncludePath_ :: Maybe FilePath
, defaultSaveFormat_ :: String
, defaultDPI_ :: Int
, interpreter_ :: String
, flags_ :: [String]
}
instance FromJSON ConfigPrecursor where
parseJSON (Object v) = ConfigPrecursor
<$> v .:? (T.pack directoryKey) .!= (defaultDirectory def)
<*> v .:? (T.pack includePathKey)
<*> v .:? (T.pack saveFormatKey) .!= (extension $ defaultSaveFormat def)
<*> v .:? (T.pack dpiKey) .!= (defaultDPI def)
<*> v .:? "interpreter" .!= (interpreter def)
<*> v .:? "flags" .!= (flags def)
parseJSON _ = fail "Could not parse the configuration"
renderConfiguration :: ConfigPrecursor -> IO Configuration
renderConfiguration prec = do
includeScript <- fromMaybe mempty $ T.readFile <$> defaultIncludePath_ prec
let saveFormat' = fromMaybe (defaultSaveFormat def) $ saveFormatFromString $ defaultSaveFormat_ prec
return $ Configuration { defaultDirectory = defaultDirectory_ prec
, defaultIncludeScript = includeScript
, defaultSaveFormat = saveFormat'
, defaultDPI = defaultDPI_ prec
, interpreter = interpreter_ prec
, flags = flags_ prec
}
configuration :: FilePath -> IO Configuration
configuration fp = loadYamlSettings [fp] [] ignoreEnv >>= renderConfiguration