{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE RankNTypes #-}
module Client.Configuration
(
Configuration(..)
, ConfigurationFailure(..)
, LayoutMode(..)
, PaddingMode(..)
, ExtensionConfiguration(..)
, configDefaults
, configServers
, configPalette
, configWindowNames
, configNickPadding
, configDownloadDir
, configMacros
, configExtensions
, configExtraHighlights
, configUrlOpener
, configIgnores
, configActivityBar
, configBellOnMention
, configHideMeta
, configKeyMap
, configLayout
, configShowPing
, configJumpModifier
, extensionPath
, extensionRtldFlags
, extensionArgs
, loadConfiguration
, getNewConfigPath
, configurationSpec
, FilePathContext
, newFilePathContext
, resolveFilePath
) where
import Client.Commands.Interpolation
import Client.Commands.Recognizer
import Client.Configuration.Colors
import Client.Configuration.Macros (macroMapSpec)
import Client.Configuration.ServerSettings
import Client.EventLoop.Actions
import Client.Image.Palette
import Config
import Config.Schema
import Control.Exception
import Control.Monad (unless)
import Control.Lens hiding (List)
import Data.Foldable (toList)
import Data.Functor.Alt ((<!>))
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import qualified Data.List.NonEmpty as NonEmpty
import Data.Maybe
import Data.Monoid (Endo(..))
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import qualified Data.Vector as Vector
import Graphics.Vty.Input.Events (Modifier(..), Key(..))
import Graphics.Vty.Attributes (Attr)
import Irc.Identifier (Identifier)
import System.Directory
import System.FilePath
import System.IO.Error
import System.Posix.DynamicLinker (RTLDFlags(..))
data Configuration = Configuration
{ _configDefaults :: ServerSettings
, _configServers :: (HashMap Text ServerSettings)
, _configPalette :: Palette
, _configWindowNames :: Text
, _configExtraHighlights :: HashSet Identifier
, _configNickPadding :: PaddingMode
, _configDownloadDir :: FilePath
, _configMacros :: Recognizer Macro
, _configExtensions :: [ExtensionConfiguration]
, _configUrlOpener :: Maybe FilePath
, _configIgnores :: [Text]
, _configActivityBar :: Bool
, _configBellOnMention :: Bool
, _configHideMeta :: Bool
, _configKeyMap :: KeyMap
, _configLayout :: LayoutMode
, _configShowPing :: Bool
, _configJumpModifier :: [Modifier]
}
deriving Show
data PaddingMode
= LeftPadding !Int
| RightPadding !Int
| NoPadding
deriving (Show)
data LayoutMode
= OneColumn
| TwoColumn
deriving Show
data ConfigurationFailure
= ConfigurationReadFailed String
| ConfigurationParseFailed FilePath String
| ConfigurationMalformed FilePath String
deriving Show
instance Exception ConfigurationFailure
data ExtensionConfiguration = ExtensionConfiguration
{ _extensionPath :: FilePath
, _extensionRtldFlags :: [RTLDFlags]
, _extensionArgs :: [Text]
}
deriving Show
makeLenses ''Configuration
makeLenses ''ExtensionConfiguration
defaultWindowNames :: Text
defaultWindowNames = "1234567890qwertyuiop!@#$%^&*()QWERTYUIOP"
getOldConfigPath :: IO FilePath
getOldConfigPath =
do dir <- getAppUserDataDirectory "glirc"
return (dir </> "config")
getNewConfigPath :: IO FilePath
getNewConfigPath =
do dir <- getXdgDirectory XdgConfig "glirc"
return (dir </> "config")
emptyConfigFile :: Text
emptyConfigFile = "{}\n"
readFileCatchNotFound ::
FilePath ->
(IOError -> IO (FilePath, Text)) ->
IO (FilePath, Text)
readFileCatchNotFound path onNotFound =
do res <- try (Text.readFile path)
case res of
Left e | isDoesNotExistError e -> onNotFound e
| otherwise -> throwIO (ConfigurationReadFailed (show e))
Right txt -> return (path, txt)
readConfigurationFile ::
Maybe FilePath ->
IO (FilePath, Text)
readConfigurationFile mbPath =
case mbPath of
Just path ->
readFileCatchNotFound path $ \e ->
throwIO (ConfigurationReadFailed (show e))
Nothing ->
do newPath <- getNewConfigPath
readFileCatchNotFound newPath $ \_ ->
do oldPath <- getOldConfigPath
readFileCatchNotFound oldPath $ \_ ->
return ("", emptyConfigFile)
loadConfiguration ::
Maybe FilePath ->
IO (Either ConfigurationFailure (FilePath, Configuration))
loadConfiguration mbPath = try $
do (path,txt) <- readConfigurationFile mbPath
def <- loadDefaultServerSettings
home <- getHomeDirectory
rawcfg <-
case parse txt of
Left e -> throwIO (ConfigurationParseFailed path (displayException e))
Right rawcfg -> return rawcfg
case loadValue configurationSpec rawcfg of
Left e -> throwIO
$ ConfigurationMalformed path
$ displayException e
Right cfg ->
do cfg' <- resolvePaths path (cfg def home)
>>= validateDirectories path
return (path, cfg')
resolvePaths :: FilePath -> Configuration -> IO Configuration
resolvePaths file cfg =
do res <- resolveFilePath <$> newFilePathContext file
let resolveServerFilePaths = over (ssTlsClientCert . mapped) res
. over (ssTlsClientKey . mapped) res
. over (ssTlsServerCert . mapped) res
. over (ssSaslEcdsaFile . mapped) res
. over (ssLogDir . mapped) res
return $! over (configExtensions . mapped . extensionPath) res
. over (configServers . mapped) resolveServerFilePaths
. over configDownloadDir res
$ cfg
validateDirectories :: FilePath -> Configuration -> IO Configuration
validateDirectories cfgPath cfg =
do isDir <- doesDirectoryExist downloadPath
unless isDir $ throwIO (ConfigurationMalformed cfgPath noDirMsg)
isWriteable <- writable <$> getPermissions downloadPath
unless isWriteable
$ throwIO (ConfigurationMalformed cfgPath noWriteableMsg)
return cfg
where
downloadPath = view configDownloadDir cfg
noDirMsg = "The download-dir section doesn't point to a directory."
noWriteableMsg = "The download-dir doesn't point to a writeable directory."
configurationSpec ::
ValueSpec (ServerSettings -> FilePath -> Configuration)
configurationSpec = sectionsSpec "config-file" $
do let sec' def name spec info = fromMaybe def <$> optSection' name spec info
identifierSetSpec = HashSet.fromList <$> listSpec identifierSpec
ssDefUpdate <- sec' id "defaults" serverSpec
"Default values for use across all server configurations"
ssUpdates <- sec' [] "servers" (listSpec serverSpec)
"Configuration parameters for IRC servers"
_configPalette <- sec' defaultPalette "palette" paletteSpec
"Customize the client color choices"
_configWindowNames <- sec' defaultWindowNames "window-names" anySpec
"Window names to use for quick jumping with jump-modifier key"
_configJumpModifier <- sec' [MMeta] "jump-modifier" modifierSpec
"Modifier used to jump to a window by name. Defaults to `meta`."
_configMacros <- sec' mempty "macros" macroMapSpec
"Programmable macro commands"
_configExtensions <- sec' [] "extensions" (listSpec extensionSpec)
"extension libraries to load at startup"
_configUrlOpener <- optSection' "url-opener" stringSpec
"External command used by /url command"
_configExtraHighlights <- sec' mempty "extra-highlights" identifierSetSpec
"Extra words to highlight in chat messages"
_configNickPadding <- sec' NoPadding "nick-padding" nickPaddingSpec
"Amount of space to reserve for nicknames in chat messages"
_configIgnores <- sec' [] "ignores" anySpec
"Set of nicknames to ignore on startup"
_configActivityBar <- sec' False "activity-bar" yesOrNoSpec
"Show channel names and message counts for activity on\
\ unfocused channels."
_configBellOnMention <- sec' False "bell-on-mention" yesOrNoSpec
"Emit bell character to terminal on mention"
_configHideMeta <- sec' False "hide-metadata" yesOrNoSpec
"Initial setting for hiding metadata on new windows"
bindings <- sec' [] "key-bindings" (listSpec keyBindingSpec)
"Extra key bindings"
_configLayout <- sec' OneColumn "layout" layoutSpec
"Initial setting for window layout"
_configShowPing <- sec' True "show-ping" yesOrNoSpec
"Initial setting for visibility of ping times"
maybeDownloadDir <- optSection' "download-dir" stringSpec
"Path to DCC download directoy. Defaults to home directory."
return (\def home ->
let _configDefaults = ssDefUpdate def
_configServers = buildServerMap _configDefaults ssUpdates
_configKeyMap = foldl (\acc f -> f acc) initialKeyMap bindings
_configDownloadDir = fromMaybe home maybeDownloadDir
in Configuration{..})
defaultPaddingSide :: Int -> PaddingMode
defaultPaddingSide = RightPadding
nickPaddingSpec :: ValueSpec PaddingMode
nickPaddingSpec = defaultPaddingSide <$> nonnegativeSpec <!> fullNickPaddingSpec
fullNickPaddingSpec :: ValueSpec PaddingMode
fullNickPaddingSpec = sectionsSpec "nick-padding" (sideSec <*> amtSec)
where
sideSpec = LeftPadding <$ atomSpec "left" <!>
RightPadding <$ atomSpec "right"
sideSec = fromMaybe defaultPaddingSide
<$> optSection' "side" sideSpec "Side to pad (default `right`)"
amtSec = reqSection' "width" nonnegativeSpec "Field width"
modifierSpec :: ValueSpec [Modifier]
modifierSpec = toList <$> oneOrNonemptySpec modifier1Spec
where
modifier1Spec = namedSpec "modifier"
$ MMeta <$ atomSpec "meta"
<!> MAlt <$ atomSpec "alt"
<!> MCtrl <$ atomSpec "ctrl"
layoutSpec :: ValueSpec LayoutMode
layoutSpec = OneColumn <$ atomSpec "one-column"
<!> TwoColumn <$ atomSpec "two-column"
keyBindingSpec :: ValueSpec (KeyMap -> KeyMap)
keyBindingSpec = actBindingSpec <!> cmdBindingSpec <!> unbindingSpec
actBindingSpec :: ValueSpec (KeyMap -> KeyMap)
actBindingSpec = sectionsSpec "action-binding" $
do ~(m,k) <- reqSection' "bind" keySpec
"Key to be bound (e.g. a, C-b, M-c C-M-d)"
a <- reqSection "action"
"Action name (see `/keymap`)"
return (addKeyBinding m k a)
cmdBindingSpec :: ValueSpec (KeyMap -> KeyMap)
cmdBindingSpec = sectionsSpec "command-binding" $
do ~(m,k) <- reqSection' "bind" keySpec
"Key to be bound (e.g. a, C-b, M-c C-M-d)"
cmd <- reqSection "command"
"Client command to execute (exclude leading `/`)"
return (addKeyBinding m k (ActCommand cmd))
unbindingSpec :: ValueSpec (KeyMap -> KeyMap)
unbindingSpec = sectionsSpec "remove-binding" $
do ~(m,k) <- reqSection' "unbind" keySpec
"Key to be unbound (e.g. a, C-b, M-c C-M-d)"
return (removeKeyBinding m k)
keySpec :: ValueSpec ([Modifier], Key)
keySpec = customSpec "emacs-key" stringSpec
$ \key -> case parseKey key of
Nothing -> Left "unknown key"
Just x -> Right x
nonnegativeSpec :: (Ord a, Num a) => ValueSpec a
nonnegativeSpec = customSpec "non-negative" numSpec
$ \x -> if x < 0 then Left "negative number"
else Right x
paletteSpec :: ValueSpec Palette
paletteSpec = sectionsSpec "palette" $
(ala Endo (foldMap . foldMap) ?? defaultPalette) <$> sequenceA fields
where
nickColorsSpec :: ValueSpec (Palette -> Palette)
nickColorsSpec = set palNicks . Vector.fromList . NonEmpty.toList
<$> nonemptySpec attrSpec
modeColorsSpec :: Lens' Palette (HashMap Char Attr) -> ValueSpec (Palette -> Palette)
modeColorsSpec l
= fmap (set l)
$ customSpec "modes" (assocSpec attrSpec)
$ fmap HashMap.fromList
. traverse (\(mode, attr) ->
case Text.unpack mode of
[m] -> Right (m, attr)
_ -> Left "expected single letter")
fields :: [SectionsSpec (Maybe (Palette -> Palette))]
fields = optSection' "nick-colors" nickColorsSpec
"Colors used to highlight nicknames"
: optSection' "cmodes" (modeColorsSpec palCModes)
"Colors used to highlight channel modes"
: optSection' "umodes" (modeColorsSpec palUModes)
"Colors used to highlight user modes"
: optSection' "snomask" (modeColorsSpec palSnomask)
"Colors used to highlight server notice mask"
: [ optSection' lbl (set l <$> attrSpec) "" | (lbl, Lens l) <- paletteMap ]
extensionSpec :: ValueSpec ExtensionConfiguration
extensionSpec = simpleExtensionSpec <!> fullExtensionSpec
defaultRtldFlags :: [RTLDFlags]
defaultRtldFlags = [RTLD_LOCAL, RTLD_NOW]
simpleExtensionSpec :: ValueSpec ExtensionConfiguration
simpleExtensionSpec =
do _extensionPath <- stringSpec
pure ExtensionConfiguration
{ _extensionRtldFlags = defaultRtldFlags
, _extensionArgs = []
, .. }
fullExtensionSpec :: ValueSpec ExtensionConfiguration
fullExtensionSpec =
sectionsSpec "extension" $
do _extensionPath <- reqSection' "path" stringSpec
"Path to shared object"
_extensionRtldFlags <- fromMaybe defaultRtldFlags <$>
optSection' "rtld-flags" (listSpec rtldFlagSpec)
"Runtime dynamic linker flags"
_extensionArgs <- fromMaybe [] <$> optSection "args"
"Extension-specific configuration arguments"
pure ExtensionConfiguration {..}
rtldFlagSpec :: ValueSpec RTLDFlags
rtldFlagSpec = namedSpec "rtld-flag"
$ RTLD_LOCAL <$ atomSpec "local"
<!> RTLD_GLOBAL <$ atomSpec "global"
<!> RTLD_NOW <$ atomSpec "now"
<!> RTLD_LAZY <$ atomSpec "lazy"
buildServerMap ::
ServerSettings ->
[ServerSettings -> ServerSettings] ->
HashMap Text ServerSettings
buildServerMap def ups =
HashMap.fromList [ (serverSettingName ss, ss) | up <- ups, let ss = up def ]
where
serverSettingName ss =
fromMaybe (views ssHostName Text.pack ss)
(view ssName ss)
data FilePathContext = FilePathContext { fpBase, fpHome :: FilePath }
newFilePathContext ::
FilePath ->
IO FilePathContext
newFilePathContext base = FilePathContext (takeDirectory base) <$> getHomeDirectory
resolveFilePath :: FilePathContext -> FilePath -> FilePath
resolveFilePath fpc path
| isAbsolute path = path
| "~":rest <- splitDirectories path = joinPath (fpHome fpc : rest)
| otherwise = fpBase fpc </> path