aboutsummaryrefslogtreecommitdiffstats
path: root/app/Main.hs
blob: 29d49538d8abc0ddb1935c9a528a5ae89f723dbb (plain) (blame)
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
{-# LANGUAGE RecordWildCards #-}

module Main where

import           Control.Concurrent              (getNumCapabilities)
import           Control.Monad                   (void)
import           Data.Monoid                     ((<>))
import           System.Directory                (createDirectoryIfMissing,
                                                  doesDirectoryExist)
import           System.Exit                     (die)
import           System.FilePath.Posix           (takeDirectory, (</>))
import           System.Info                     (os)
import           System.Posix.IO                 (OpenMode (..), closeFd,
                                                  defaultFileFlags, dupTo,
                                                  openFd, stdError, stdInput,
                                                  stdOutput)
import           System.Posix.Process            (forkProcess)
import           System.Posix.Types              (Fd)

import           Options.Applicative

import           Network.WireGuard.Daemon        (runDaemon)
import           Network.WireGuard.Foreign.Tun   (openTun)
import           Network.WireGuard.Internal.Util (catchIOExceptionAnd)

data Opts = Opts
          { foreground :: Bool
          , intfName   :: String
          }

parser :: ParserInfo Opts
parser = info (helper <*> opts) fullDesc
  where
    opts = Opts <$> _foreground
                <*> _intfName

    _foreground = switch
                ( long "foreground"
               <> short 'f'
               <> help "run in the foreground")

    _intfName = argument str
              ( metavar "interface"
             <> help ("device interface name (e.g. " ++ intfNameExample ++ ")"))

    intfNameExample | os == "darwin" = "utun1"
                    | otherwise      = "wg0"


main :: IO ()
main = do
    Opts{..} <- execParser parser

    runPath <- maybe (die "failed to find path to bind socket") return =<< findVarRun
    let sockPath = runPath </> "wireguard" </> (intfName ++ ".sock")
    createDirectoryIfMissing False (takeDirectory sockPath)

    fds <- openTun intfName =<< getNumCapabilities

    let runner daemon | foreground = daemon
                      | otherwise  = void $ forkProcess $ do
                          mapM_ redirectToNull [stdInput, stdOutput, stdError]
                          daemon

    runner $ runDaemon intfName sockPath fds

redirectToNull :: Fd -> IO ()
redirectToNull fd = catchIOExceptionAnd (return ()) $ do
    nullFd <- openFd "/dev/null" ReadWrite Nothing defaultFileFlags
    closeFd fd
    void $ dupTo nullFd fd

findVarRun :: IO (Maybe FilePath)
findVarRun = loop ["/var/run", "/run"]
  where
    loop [] = return Nothing
    loop (d:ds) = do
        exists <- doesDirectoryExist d
        if exists
          then return (Just d)
          else loop ds