Matthias Andreas Benkard | 262110d | 2021-08-24 06:35:55 +0200 | [diff] [blame] | 1 | {-# LANGUAGE BlockArguments #-} |
| 2 | {-# LANGUAGE DuplicateRecordFields #-} |
| 3 | {-# LANGUAGE LambdaCase #-} |
| 4 | {-# LANGUAGE TypeOperators #-} |
| 5 | {-# LANGUAGE UndecidableInstances #-} |
| 6 | |
| 7 | module Mulkup.Bupstash (BupItem(..), Bupstash (..), bupPut, bupGc, bupList, bupRemove, BupFilter (..), runBupstash, bupItemUTCTime) where |
| 8 | |
| 9 | import Mulkup.Config (MulkupConfig (..)) |
| 10 | import Mulkup.Prelude hiding (put) |
| 11 | import Optics |
| 12 | import Polysemy |
| 13 | import Polysemy.Reader (Reader, asks) |
| 14 | import Turtle hiding (err, x) |
| 15 | import Data.Aeson (FromJSON, eitherDecode) |
| 16 | import Polysemy.Error (Error, throw) |
| 17 | import Data.Text (pack, unpack) |
| 18 | import Mulkup.Logging |
| 19 | import Colog.Polysemy (Log) |
| 20 | import Colog (Message) |
| 21 | import Data.Time |
| 22 | import Data.Time.Clock.POSIX |
| 23 | |
| 24 | -- * API |
| 25 | |
| 26 | data BupItem = BupItem |
| 27 | { id :: Text, |
| 28 | unix_timestamp_millis :: Integer, |
| 29 | tags :: Map String String |
| 30 | } |
| 31 | deriving stock (Generic, Show) |
| 32 | deriving anyclass (FromJSON) |
| 33 | |
| 34 | data BupFilter = BupFilter |
| 35 | { labels :: [(Text, Text)], |
| 36 | minimumAge :: Maybe Text |
| 37 | } |
| 38 | |
| 39 | makeFieldLabelsNoPrefix ''BupFilter |
| 40 | |
| 41 | data Bupstash m a where |
| 42 | BupGc :: Bupstash m () |
| 43 | BupPut :: Text -> [Text] -> [(Text, Text)] -> Bupstash m () |
| 44 | BupList :: BupFilter -> Bupstash m [BupItem] |
| 45 | BupRemove :: [Text] -> Bupstash m () |
| 46 | |
| 47 | makeSem ''Bupstash |
| 48 | |
| 49 | -- * Smart Accessors |
| 50 | |
| 51 | bupItemUTCTime :: BupItem -> UTCTime |
| 52 | bupItemUTCTime item = |
| 53 | posixSecondsToUTCTime $ |
| 54 | secondsToNominalDiffTime $ |
| 55 | fromInteger (item ^. #unix_timestamp_millis) / 1000 |
| 56 | |
| 57 | -- * Implementation |
| 58 | |
| 59 | -- | Runs a 'Bupstash' using the “bupstash” CLI command. |
| 60 | runBupstash :: (Member (Error Text) r, Member (Log Message) r, Member (Embed IO) r, Member (Reader MulkupConfig) r) => Sem (Bupstash ': r) a -> Sem r a |
| 61 | runBupstash = interpret \case |
| 62 | BupGc -> |
| 63 | procs "bupstash" ["gc"] empty |
| 64 | |
| 65 | BupPut baseDir exclusions labels -> do |
| 66 | host <- getHost |
| 67 | procs "bupstash" (["put", "--xattrs"] ++ map exclusionArg exclusions ++ map labelArg labels ++ [labelArg ("host", host)] ++ [baseDir]) empty |
| 68 | |
| 69 | BupList bupFilter -> do |
| 70 | host <- getHost |
| 71 | out <- strict $ inproc "bupstash" (["list", "--format=jsonl1"] ++ filterArgs host bupFilter) empty |
| 72 | let parsedItems = map parseItem (patchLines (lines out)) |
| 73 | forM parsedItems \case |
| 74 | Left err -> do |
| 75 | let errtext = pack err |
| 76 | logError errtext |
| 77 | throw errtext |
| 78 | Right x -> |
| 79 | return x |
| 80 | |
| 81 | BupRemove ids -> do |
| 82 | procs "bupstash" ["rm", "--ids-from-stdin"] (select (map unsafeTextToLine ids)) |
| 83 | |
| 84 | where |
| 85 | getHost :: Member (Reader MulkupConfig) r => Sem r Text |
| 86 | getHost = |
| 87 | asks @MulkupConfig (^. #host) |
| 88 | |
| 89 | -- | Fixes up the buggy two-line output that Buptash produces in |
| 90 | -- jsonl1 output mode. |
| 91 | -- |
| 92 | -- See: https://github.com/andrewchambers/bupstash/pull/241 |
| 93 | patchLines :: [Text] -> [Text] |
| 94 | patchLines = concatMap patchLine |
| 95 | where |
| 96 | patchLine :: Text -> [Text] |
| 97 | patchLine line |
| 98 | | line == "}" = |
| 99 | [] |
| 100 | | length (filter (== '}') $ unpack line) < length (filter (== '{') $ unpack line) = |
| 101 | [line <> "}"] |
| 102 | | otherwise = |
| 103 | [line] |
| 104 | |
| 105 | labelArg :: (Text, Text) -> Text |
| 106 | labelArg (key, value) = key <> "=" <> value |
| 107 | |
| 108 | exclusionArg :: Text -> Text |
| 109 | exclusionArg = ("--exclude=" <>) |
| 110 | |
| 111 | filterArgs :: Text -> BupFilter -> [Text] |
| 112 | filterArgs host (BupFilter labels minimumAge) = |
| 113 | [labelArg ("host", host)] ++ |
| 114 | concatMap (\label -> ["and", labelArg label]) labels ++ |
| 115 | concatMap (\x -> ["and", "older-than", x]) minimumAge |
| 116 | |
| 117 | parseItem :: Text -> Either String BupItem |
| 118 | parseItem = eitherDecode . encodeUtf8 |