{-# LANGUAGE OverloadedStrings #-} module CLI.Commands.ChildSA where import Control.Lens ((.=)) import Control.Monad (void, when) import Control.Monad.IO.Class (liftIO) import Control.Monad.Trans.Maybe (MaybeT(..), runMaybeT) import CLI.Commands.Common import CLI.Types import Data.Default (def) import Data.Maybe (fromMaybe) import Data.Text (Text,unpack) import Control.Monad.State.Strict (StateT, get, lift) import StrongSwan.SQL import System.Console.StructuredCLI hiding (Commands) saAction :: (Monad m) => Validator m SAAction saAction = return . fromName saMode :: (Monad m) => Validator m SAMode saMode = return . fromName cfgChildSA :: Commands () cfgChildSA = do cfgLifeTime cfgRekeyTime cfgJitter cfgUpDown cfgHostAccess cfgSAMode cfgStartAction cfgDPDAction cfgCloseAction cfgIPCompression cfgReqID cfgMark setChildSA :: Text -> StateT AppState IO Action setChildSA name = do childSA <- setConfig findChildSAConfigByName def { _childSAName = name } name ipsecSettings . getChildSAConfig .= childSA flush .= Just flushChildSA return NewLevel showChildSA :: Commands () showChildSA = command "show" "Show this child SA configuration" showChildSA' showChildSA' :: StateT AppState IO Action showChildSA' = do AppState{_ipsecSettings = IPSecSettings{_getChildSAConfig=ChildSAConfig{..}}} <- get let iD = _childSAId >>= return . show liftIO $ do putStr "Child SA " when (_childSAName /= "") $ putStr $ '\'':unpack _childSAName ++ "\' " putStrLn $ "(ID: " ++ fromMaybe "*uncommitted*" iD ++ ")" putStrLn $ "=================================="; putStrLn $ "Lifetime: " ++ show _childSALifeTime putStrLn $ "Rekeytime: " ++ show _childSARekeyTime putStrLn $ "Jitter: " ++ show _childSAJitter putStrLn $ "UpDown: " ++ maybe "" unpack _childSAUpDown putStrLn $ "HostAccess: " ++ showEnabled _childSAHostAccess putStrLn $ "SA Mode: " ++ nameOf _childSAMode putStrLn $ "Start Action: " ++ nameOf _childSAStartAction putStrLn $ "DPD Action: " ++ nameOf _childSADPDAction putStrLn $ "Close Action: " ++ nameOf _childSACloseAction putStrLn $ "IP compression: " ++ showEnabled _childSAIPCompression putStrLn $ "Request ID: " ++ show _childSAReqID return NoAction cfgLifeTime :: Commands () cfgLifeTime = param "lifetime" "" integer $ \lifetime -> do ipsecSettings . getChildSAConfig . childSALifeTime .= lifetime flushIt cfgRekeyTime :: Commands () cfgRekeyTime = param "rekeytime" "" integer $ \timeout -> do ipsecSettings . getChildSAConfig . childSARekeyTime .= timeout flushIt cfgJitter :: Commands () cfgJitter = param "jitter" "" integer $ \jitter -> do ipsecSettings . getChildSAConfig . childSAJitter .= jitter flushIt cfgUpDown :: Commands () cfgUpDown = param "updown-script" "" string $ \script -> do ipsecSettings . getChildSAConfig . childSAUpDown .= Just script flushIt cfgSAMode :: Commands () cfgSAMode = param "mode" "" saMode $ \mode -> do ipsecSettings . getChildSAConfig . childSAMode .= mode flushIt cfgHostAccess :: Commands () cfgHostAccess = param "host-access" "" readEnabled $ \status -> do ipsecSettings . getChildSAConfig . childSAHostAccess .= status flushIt cfgStartAction :: Commands () cfgStartAction = param "start-action" "" saAction $ \action -> do ipsecSettings . getChildSAConfig . childSAStartAction .= action flushIt cfgDPDAction :: Commands () cfgDPDAction = param "dpd-action" "" saAction $ \action -> do ipsecSettings . getChildSAConfig . childSADPDAction .= action flushIt cfgCloseAction :: Commands () cfgCloseAction = param "close-action" "" saAction $ \action -> do ipsecSettings . getChildSAConfig . childSACloseAction .= action flushIt cfgIPCompression :: Commands () cfgIPCompression = param "ip-compression" "" readEnabled $ \status -> do ipsecSettings . getChildSAConfig . childSAIPCompression .= status flushIt cfgReqID :: Commands () cfgReqID = param "req-id" "" integer $ \reqID -> do ipsecSettings . getChildSAConfig . childSAReqID .= reqID flushIt cfgMark :: Commands () cfgMark = param "mark" "" string $ \mark -> do ipsecSettings . getChildSAConfig . childSAMark .= Just mark flushIt flushChildSA :: StateT AppState IO Action flushChildSA = do AppState{_ipsecSettings = IPSecSettings{_getChildSAConfig=childSA@ChildSAConfig{..}}, ..} <- get Result {response = OK {..}} <- lift $ writeChildSAConfig childSA _dbContext when (okAffectedRows /= 1 ) $ liftIO . putStrLn $ "(1) warning: affected " ++ show okAffectedRows ++ " (expected 1)" void . runMaybeT $ do childSA':xs <- findChildSAConfigByName _childSAName _dbContext when (xs /= []) $ liftIO . putStrLn $ "Warning: more than one child SA config named " ++ unpack _childSAName ++ " found" lift $ ipsecSettings . getChildSAConfig .= childSA' return NoAction