summaryrefslogtreecommitdiff
path: root/hs/src/Config.hs
blob: e0b846cbaba6d5a57efa8564c65f21ad858b0f28 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
{-# LANGUAGE TemplateHaskell
           , OverloadedStrings
           , FlexibleInstances
  #-}

module Config where

import Control.Lens
import Data.Map (Map)
import qualified Data.Map as M
import Network.URI (URI, parseURI)
import Options.Applicative
import Data.Ini
import Data.Maybe (isJust, fromMaybe, fromJust)
import Data.String
import Data.Text (Text, unpack)

data Args = Args
    { indir    :: Maybe String
    , outdir   :: Maybe String
    , conffile :: Maybe String
    , webp     :: Maybe String
    } deriving (Show)

instance IsString (Maybe String) where
  fromString a = Just a

argp :: Parser Args
argp = Args
    <$> strOption (long "indir"  <> short 'i' <> help "Input Directory"           <> metavar "DIR"  <> value Nothing)
    <*> strOption (long "outdir" <> short 'o' <> help "Output Directory"          <> metavar "DIR"  <> value Nothing)
    <*> strOption (long "conf"   <> short 'c' <> help "Alternative Configuration" <> metavar "CONF" <> value Nothing)
    <*> strOption (long "webp"   <> help "Prefix for web" <> metavar "PREFIX" <> value Nothing)

opts = info (argp <**> helper)
            (fullDesc
            <> progDesc "Build Vimwiki"
            <> header "build - build vimwiki")


data Configuration = Configuration
    { _output :: OutputConfig
    , _data'  :: DataConfig
    , _wikis :: Map String URI
    } deriving (Eq, Show)

data DataConfig = DataConfig
    -- Source of vimwiki files
    { _inputDir  :: FilePath
    -- where generated pages should be placed
    , _outputDir :: FilePath
    } deriving (Eq, Show)

data OutputConfig = OutputConfig
    { _mu4eURL     :: Maybe String
    , _xapianOmega :: Maybe String
    -- Are we in a subdirectory from the web root?
    , _webPath     :: String
    , _manProvider  :: Maybe String
    } deriving (Eq, Show)

makeLenses ''Configuration
makeLenses ''DataConfig
makeLenses ''OutputConfig

--
-- either to maybe
etm :: Either a b -> Maybe b
etm (Left _)  = Nothing
etm (Right a) = Just a

fromRight (Right x) = x
fromRight (Left _)  = error "fromRight called on left value"

parseURIs :: [(Text, String)] -> Map String URI
parseURIs lst = lst & fmap (_2 %~ parseURI)
                    & filter (isJust . snd)
                    & fmap (_2 %~ fromJust)
                    & fmap (_1 %~ unpack)
                    & M.fromList

confParser :: Ini -> Configuration
confParser ini =
    Configuration
        { _output = OutputConfig { _mu4eURL     = d "Output" "mu4eURL"
                                 , _xapianOmega = d "Output" "xapianOmega"
                                 , _webPath     = fromMaybe "" $ d "Output" "webPath"
                                 , _manProvider = d "Output" "manProvider"
                                 }
        , _data' = if "Data" `elem` sections ini
                    then DataConfig
                            -- Thi4s will crash if key is missing
                            { _inputDir  = f "Data" "inputDir"
                            , _outputDir = f "Data" "outputDir"
                            }
                    else (_data' defaultConf)
        , _wikis = case keys "Wikis" ini of
                     Left _     -> mempty
                     -- This includes a fromRight, but is saze since
                     -- we already checked that the key existed
                     Right keys -> parseURIs $ zip keys $ f "Wikis" <$> keys
        }

    where d a b = etm $ unpack <$> lookupValue a b ini
          f a b = unpack . fromRight $ lookupValue a b ini

runParser :: Text -> Either String Configuration
runParser t = confParser <$> parseIni t

parseCmdline = execParser opts

defaultConf = Configuration
    { _output = OutputConfig
                { _mu4eURL     = Nothing
                , _xapianOmega = Nothing
                , _webPath      = ""
                , _manProvider = Nothing
                }
    , _data' = DataConfig
                { _inputDir  = ""
                , _outputDir = ""
                }
    , _wikis = mempty
    }