-- pi-hoole: lightweight access-control for pijul -- Copyright (C) 2018 Thomas Letan -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU Affero General Public License as published -- by the Free Software Foundation, either version 3 of the License, or -- (at your option) any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU Affero General Public License for more details. -- -- You should have received a copy of the GNU Affero General Public License -- along with this program. If not, see . {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} module Main where import Control.Monad (void) import Data.Map.Strict (Map) import qualified Data.Map.Strict as M (fromList, traverseWithKey) import Data.Set (Set) import qualified Data.Set as S (fromList) import Data.Text (Text, append, pack, unpack) import qualified Data.Text.IO as T (getLine) import Data.Void (Void) import Data.Yaml (decodeFile) import PiHoole import System.Directory (XdgDirectory (..), getXdgDirectory) import System.Environment (getArgs) import Text.Megaparsec (parseTest) ------------------------------------------------------------------------------- main :: IO () main = getConfiguration >>= \case Just cfg -> getArgs >>= \case [ "--license" ] -> putStrLn license [ user, "" ] -> case parseUserName (pack user) of Just user@(UserName username) -> do putStrLn $ "Connected as " ++ unpack username ++ "\n" printPrivileges (hasPrivileges (User user) cfg) putStrLn "" [ user, cmd ] -> case (parseUserName (pack user), parsePijul (pack cmd)) of (Just user, Just cmd) -> pijulProxy cfg user cmd (Nothing, _) -> putStrLn $ user ++ " is not a valid role" (_, Nothing) -> putStrLn $ cmd ++ " is not a valid pijul command" _ -> putStrLn "incorrect shell command" Nothing -> putStrLn "could not parse the configuration file" ------------------------------------------------------------------------------- ------------------------------------------------------------------------------- printPrivileges :: Map Repo Privilege -> IO () printPrivileges map = void $ M.traverseWithKey printPrivilege map where printPrivilege (Repo repo) priv = putStrLn $ "- " ++ repo ++ ": " ++ unpack (privilegeToText priv) getConfiguration :: IO (Maybe Configuration) getConfiguration = getXdgDirectory XdgConfig "pi-hoole/config.yaml" >>= decodeFile decodeLimes :: FilePath -> IO (Maybe Configuration) decodeLimes = decodeFile pijulProxy :: Configuration -> UserName -> Pijul -> IO () pijulProxy cfg user cmd | checkPrivilege user cmd cfg = callPijul cmd | otherwise = putStrLn "nah" license :: String license = unlines [ "Copyright (C) 2018 Thomas Letan " , "" , "This program is free software: you can redistribute it and/or modify" , "it under the terms of the GNU Affero General Public License as published" , "by the Free Software Foundation, either version 3 of the License, or" , "(at your option) any later version." , "" , "This program is distributed in the hope that it will be useful," , "but WITHOUT ANY WARRANTY; without even the implied warranty of" , "MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the" , "GNU Affero General Public License for more details." , "" , "You should have received a copy of the GNU Affero General Public License" , "along with this program. If not, see ." ] -------------------------------------------------------------------------------