-
Notifications
You must be signed in to change notification settings - Fork 2
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Signed-off-by: Magic_RB <[email protected]>
- Loading branch information
Showing
8 changed files
with
735 additions
and
6 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,121 @@ | ||
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io> | ||
-- | ||
-- SPDX-License-Identifier: MPL-2.0 | ||
|
||
module Backend.Debug | ||
( DebugBackend | ||
, debugCodec | ||
) where | ||
|
||
import qualified Data.Text as T | ||
import Toml (TomlCodec) | ||
import qualified Toml | ||
import Backend | ||
import qualified Data.HashMap.Lazy as HS | ||
import Validation (Validation(Failure, Success)) | ||
import Backends | ||
import Control.Lens | ||
import Polysemy | ||
import Entry (Entry) | ||
import Coffer.Path | ||
import Data.Text (Text) | ||
|
||
data DebugBackend = | ||
DebugBackend | ||
{ dSubType :: T.Text | ||
, dSubBackend :: SomeBackend | ||
} | ||
deriving stock (Show) | ||
|
||
debugCodec :: TomlCodec DebugBackend | ||
debugCodec = Toml.Codec input output | ||
where input :: Toml.TomlEnv DebugBackend | ||
input toml = case HS.lookup "sub_type" $ Toml.tomlPairs toml of | ||
Just x -> | ||
case Toml.backward Toml._Text x of | ||
Right t -> | ||
case supportedBackends t of | ||
Right y -> | ||
let newToml = toml { Toml.tomlPairs = | ||
Toml.tomlPairs toml | ||
& HS.delete "sub_type" | ||
} | ||
in | ||
case y newToml of | ||
Success b -> Success $ DebugBackend | ||
{ dSubType = t | ||
, dSubBackend = b | ||
} | ||
Failure e -> Failure e | ||
Left e -> | ||
Failure | ||
[ Toml.BiMapError "type" e | ||
] | ||
Left e -> | ||
Failure | ||
[ Toml.BiMapError "type" e | ||
] | ||
Nothing -> | ||
Failure | ||
[ Toml.BiMapError "sub_type" $ | ||
Toml.ArbitraryError | ||
"Debug backend doesn't have a `sub_type` key" | ||
] | ||
output :: DebugBackend -> Toml.TomlState DebugBackend | ||
output debugBackend = | ||
case dSubBackend debugBackend of | ||
SomeBackend (be :: a) -> do | ||
Toml.codecWrite (Toml.text "type") "debug" | ||
Toml.codecWrite (Toml.text "sub_type") (dSubType debugBackend) | ||
Toml.codecWrite (_codec @a) be | ||
undefined | ||
|
||
dbWriteSecret | ||
:: Effects r => DebugBackend -> Entry -> Sem r () | ||
dbWriteSecret b entry = unSubBackend b $ \(SomeBackend backend) -> do | ||
embed $ putStrLn ("WriteSecret: \n" <> show entry) | ||
_writeSecret backend entry | ||
|
||
dbReadSecret | ||
:: Effects r => DebugBackend -> EntryPath -> Sem r (Maybe Entry) | ||
dbReadSecret b path = unSubBackend b $ \(SomeBackend backend) -> do | ||
embed $ putStrLn ("ReadSecret: " <> show path) | ||
_readSecret backend path >>= showPass "out: " | ||
|
||
dbListSecrets | ||
:: Effects r => DebugBackend -> Path -> Sem r (Maybe [Text]) | ||
dbListSecrets b path = unSubBackend b $ \(SomeBackend backend) -> do | ||
embed $ putStrLn ("ListSecrets: " <> show path) | ||
_listSecrets backend path >>= showPass "out: " | ||
|
||
dbDeleteSecret | ||
:: Effects r => DebugBackend -> EntryPath -> Sem r () | ||
dbDeleteSecret b path = unSubBackend b $ \(SomeBackend backend) -> do | ||
embed $ putStrLn ("DeleteSecret: " <> show path) | ||
_deleteSecret backend path | ||
|
||
unSubBackend | ||
:: DebugBackend | ||
-> (SomeBackend -> a) | ||
-> a | ||
unSubBackend b f = f (dSubBackend b) | ||
|
||
showPass | ||
:: Member (Embed IO) r | ||
=> Show a | ||
=> T.Text | ||
-> a | ||
-> Sem r a | ||
showPass txt a = do | ||
let atxt = T.pack $ show a | ||
embed $ putStrLn (T.unpack $ txt <> atxt) | ||
pure a | ||
|
||
|
||
instance Backend DebugBackend where | ||
_name debugBackend = (\(SomeBackend x) -> _name x) $ dSubBackend debugBackend | ||
_codec = debugCodec | ||
_writeSecret = dbWriteSecret | ||
_readSecret = dbReadSecret | ||
_listSecrets = dbListSecrets | ||
_deleteSecret = dbDeleteSecret |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,165 @@ | ||
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io> | ||
-- | ||
-- SPDX-License-Identifier: MPL-2.0 | ||
|
||
{-# LANGUAGE ImportQualifiedPost #-} | ||
module Backend.Pass | ||
( PassBackend ) where | ||
import Data.Text qualified as T | ||
import Toml (TomlCodec) | ||
import Toml qualified | ||
import Backend | ||
import BackendName | ||
import Polysemy | ||
import Polysemy.Error | ||
import Error | ||
import System.Process.Typed | ||
import Data.Maybe | ||
import Control.Lens | ||
import qualified Entry as E | ||
import Entry.Pass | ||
import qualified Coffer.Path as P | ||
import Fmt (build, fmt) | ||
import qualified Data.Text.Encoding as T | ||
import qualified Data.ByteString.Lazy as BS | ||
import System.FilePath (makeRelative) | ||
import System.IO.Error (isDoesNotExistError) | ||
import Control.Exception (IOException) | ||
import Data.Text.Encoding (encodeUtf8) | ||
import Effect.Fs | ||
import qualified System.Directory as D | ||
import Coffer.Path | ||
import Entry (Entry) | ||
|
||
data PassBackend = | ||
PassBackend | ||
{ pbName :: BackendName | ||
, pbStoreDir :: FilePath | ||
, pbPassExe :: Maybe FilePath | ||
} | ||
deriving stock (Show) | ||
|
||
passCodec :: TomlCodec PassBackend | ||
passCodec = | ||
PassBackend | ||
<$> backendNameCodec "name" Toml..= pbName | ||
<*> Toml.string "store_dir" Toml..= pbStoreDir | ||
<*> Toml.dimatch fPathToT tToFPath (Toml.text "pass_exe") Toml..= pbPassExe | ||
where tToFPath = Just . T.unpack | ||
fPathToT = | ||
\case | ||
Just a -> Just $ T.pack a | ||
Nothing -> Nothing | ||
|
||
|
||
verifyPassStore | ||
:: Member (Error CofferError) r | ||
=> Member (Embed IO) r | ||
=> FilePath | ||
-> Sem r () | ||
verifyPassStore storeDir = | ||
res >>= \case | ||
Left e -> throw $ OtherError (show e & T.pack) | ||
Right (Just _) -> pure () | ||
Right Nothing -> throw . OtherError $ | ||
"You must first initialize the password store at: " <> T.pack storeDir | ||
where | ||
res :: Member (Embed IO) r | ||
=> Sem r (Either FsError (Maybe (Node' ()))) | ||
res = runError @FsError . runFsInIO $ do | ||
nodeExists (stringToPath $ storeDir <> "/.gpg-id") | ||
|
||
pbWriteSecret | ||
:: Effects r => PassBackend -> Entry -> Sem r () | ||
pbWriteSecret backend entry = do | ||
let passExe = pbPassExe backend | ||
let storeDir = pbStoreDir backend | ||
verifyPassStore storeDir | ||
|
||
let input = | ||
entry ^. re E.entry . re passTextPrism | ||
& encodeUtf8 | ||
& BS.fromStrict | ||
(exitCode, _stdout, stderr) <- | ||
proc (fromMaybe "pass" passExe) | ||
[ "insert" | ||
, "-mf" | ||
, entry ^. E.path & P.entryPathAsPath & build & fmt | ||
] | ||
& setStdin (byteStringInput input) | ||
& setEnv [("PASSWORD_STORE_DIR", storeDir)] | ||
& readProcess | ||
|
||
case exitCode of | ||
ExitSuccess -> pure () | ||
ExitFailure _i -> throw $ OtherError (T.decodeUtf8 $ BS.toStrict stderr) | ||
|
||
pure () | ||
|
||
pbReadSecret | ||
:: Effects r => PassBackend -> EntryPath -> Sem r (Maybe Entry) | ||
pbReadSecret backend path = do | ||
let passExe = pbPassExe backend | ||
let storeDir = pbStoreDir backend | ||
verifyPassStore storeDir | ||
|
||
(exitCode, stdout, stderr) <- | ||
proc (fromMaybe "pass" passExe) | ||
[ "show" | ||
, path & P.entryPathAsPath & build & fmt | ||
] | ||
& setEnv [("PASSWORD_STORE_DIR", storeDir)] | ||
& readProcess | ||
|
||
case exitCode of | ||
ExitSuccess -> | ||
pure $ T.decodeUtf8 (BS.toStrict stdout) ^? passTextPrism . E.entry | ||
ExitFailure 1 -> | ||
pure Nothing | ||
ExitFailure _e -> | ||
throw $ OtherError (T.decodeUtf8 $ BS.toStrict stderr) | ||
|
||
pbListSecrets | ||
:: Effects r => PassBackend -> Path -> Sem r (Maybe [T.Text]) | ||
pbListSecrets backend path = do | ||
let storeDir = pbStoreDir backend | ||
verifyPassStore storeDir | ||
|
||
let fpath = storeDir <> (path & build & fmt) | ||
contents <- runError (fromException @IOException $ D.listDirectory fpath) | ||
>>= (\case Left e -> | ||
if | isDoesNotExistError e -> pure Nothing | ||
| True -> throw $ OtherError (T.pack $ show e) | ||
Right v -> pure $ Just v) | ||
<&> (\a -> a <&> map (makeRelative fpath)) | ||
|
||
pure $ contents <&> map (T.dropEnd 4 . T.pack) | ||
|
||
pbDeleteSecret | ||
:: Effects r => PassBackend -> EntryPath -> Sem r () | ||
pbDeleteSecret backend path = do | ||
let passExe = pbPassExe backend | ||
let storeDir = pbStoreDir backend | ||
verifyPassStore storeDir | ||
|
||
(exitCode, _stdout, stderr) <- | ||
proc (fromMaybe "pass" passExe) | ||
[ "rm" | ||
, "-f" | ||
, path & P.entryPathAsPath & build & fmt | ||
] | ||
& setEnv [("PASSWORD_STORE_DIR", storeDir)] | ||
& readProcess | ||
|
||
case exitCode of | ||
ExitSuccess -> pure () | ||
ExitFailure _e -> throw $ OtherError (T.decodeUtf8 $ BS.toStrict stderr) | ||
|
||
|
||
instance Backend PassBackend where | ||
_name kvBackend = pbName kvBackend | ||
_codec = passCodec | ||
_writeSecret = pbWriteSecret | ||
_readSecret = pbReadSecret | ||
_listSecrets = pbListSecrets | ||
_deleteSecret = pbDeleteSecret |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Oops, something went wrong.