summaryrefslogtreecommitdiff
path: root/adjmix/Adjmix.hs
blob: 5133973f2bff2362f40483fa14e7f01f8c4298b4 (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
{-# LANGUAGE RecordWildCards, ApplicativeDo #-}

import Options.Applicative

import System.FilePath
import System.FileLock

import Data.Char
import Data.Monoid
import Data.List

import Trivmix.Types


data Options = Options
               { baseDirectory :: FilePath
               , targetDirectory :: FilePath
               , levelFile :: FilePath
               , adjustment :: Adjustment Level
               }


optionParser :: Parser Options
optionParser = do
  baseDirectory <- strOption $ mconcat
    [ long "base", metavar "DIRECTORY", showDefault
    , value "/dev/shm/mix"
    , help "Base directory"
    ]
  levelFile <- strOption $ mconcat
    [ long "level", short 'l', metavar "FILENAME", showDefault
    , value "level"
    , help "Filename of the level file"
    ]
  targetDirectory <- strArgument $ mconcat
    [ metavar "DIRECTORY"
    , help "Directory relative to ‘--base’ containing the level file"
    ]
  adjustment <- getAlt . mconcat $ map Alt
    [ Set <$> option auto (mconcat
                           [ long "set", short 'o', metavar "LEVEL"
                           , help "Overwrite the current level"
                           ])
    , Add <$> option auto (mconcat
                           [ long "add", short 'a', metavar "LEVEL"
                           , help "Add to the current level"
                           ])
    , Sub <$> option auto (mconcat
                           [ long "sub", short 's', metavar "LEVEL"
                           , help "Subtract from the current level"
                           ])
    , let
        adjMode = getAlt . mconcat $ map Alt
          [ flag' Add (mconcat
                       [ long "inc", short 'i'
                       , help "Increase level by a preset amount (see ‘--by’)"
                       ])
          , flag' Sub (mconcat
                       [ long "dec", short 'd'
                       , help "Decrease level by a preset amount (see ‘--by’)"
                       ])
          ]
        adjBy = option auto (mconcat
                             [ long "by", short 'b', metavar "LEVEL", value (read "2.5dB"), showDefault
                             , help "Value to increase/decrease level by when using ‘--inc’ or ‘--dec’"
                             ])
      in adjMode <*> adjBy
    ]
  return Options{..}

main :: IO ()
main = execParser opts >>= adjmix
  where
    opts = info (helper <*> optionParser) $ mconcat
      [ progDesc "Adjust the level file of a trivmix"
      , header "Adjmix — A trivial interface to a trivial mixer"
      , fullDesc
      ]

adjmix :: Options -> IO ()
adjmix Options{..} = withFileLock levelFile' Exclusive . const $ do
  oldLevel <- readFile levelFile' >>= readIO . stripSpace
  let newLevel = oldLevel `doAdjustment` adjustment
  writeFile levelFile' $ show newLevel ++ "\n"
  where
    levelFile' = baseDirectory </> targetDirectory </> levelFile
    stripSpace = dropWhile isSpace . dropWhileEnd isSpace