blob: 22ae70ee1a4fe499f9f9d31ec24f12d1224190b8 [file] [log] [blame]
Matthias Andreas Benkard262110d2021-08-24 06:35:55 +02001{-# LANGUAGE BlockArguments #-}
2{-# LANGUAGE DuplicateRecordFields #-}
3{-# LANGUAGE LambdaCase #-}
4{-# LANGUAGE TypeOperators #-}
5{-# LANGUAGE UndecidableInstances #-}
6
7module Mulkup.Bupstash (BupItem(..), Bupstash (..), bupPut, bupGc, bupList, bupRemove, BupFilter (..), runBupstash, bupItemUTCTime) where
8
9import Mulkup.Config (MulkupConfig (..))
10import Mulkup.Prelude hiding (put)
11import Optics
12import Polysemy
13import Polysemy.Reader (Reader, asks)
14import Turtle hiding (err, x)
15import Data.Aeson (FromJSON, eitherDecode)
16import Polysemy.Error (Error, throw)
17import Data.Text (pack, unpack)
18import Mulkup.Logging
19import Colog.Polysemy (Log)
20import Colog (Message)
21import Data.Time
22import Data.Time.Clock.POSIX
23
24-- * API
25
26data 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
34data BupFilter = BupFilter
35 { labels :: [(Text, Text)],
36 minimumAge :: Maybe Text
37 }
38
39makeFieldLabelsNoPrefix ''BupFilter
40
41data 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
47makeSem ''Bupstash
48
49-- * Smart Accessors
50
51bupItemUTCTime :: BupItem -> UTCTime
52bupItemUTCTime 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.
60runBupstash :: (Member (Error Text) r, Member (Log Message) r, Member (Embed IO) r, Member (Reader MulkupConfig) r) => Sem (Bupstash ': r) a -> Sem r a
61runBupstash = 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
Matthias Andreas Benkarde1d0bbb2021-08-24 20:42:38 +020082 forM_ ids $ \id' -> do
83 procs "bupstash" ["rm", labelArg ("id", id')] empty
Matthias Andreas Benkard262110d2021-08-24 06:35:55 +020084
85 where
86 getHost :: Member (Reader MulkupConfig) r => Sem r Text
87 getHost =
88 asks @MulkupConfig (^. #host)
89
90-- | Fixes up the buggy two-line output that Buptash produces in
91-- jsonl1 output mode.
92--
93-- See: https://github.com/andrewchambers/bupstash/pull/241
94patchLines :: [Text] -> [Text]
95patchLines = concatMap patchLine
96 where
97 patchLine :: Text -> [Text]
98 patchLine line
99 | line == "}" =
100 []
101 | length (filter (== '}') $ unpack line) < length (filter (== '{') $ unpack line) =
102 [line <> "}"]
103 | otherwise =
104 [line]
105
106labelArg :: (Text, Text) -> Text
107labelArg (key, value) = key <> "=" <> value
108
109exclusionArg :: Text -> Text
110exclusionArg = ("--exclude=" <>)
111
112filterArgs :: Text -> BupFilter -> [Text]
113filterArgs host (BupFilter labels minimumAge) =
114 [labelArg ("host", host)] ++
115 concatMap (\label -> ["and", labelArg label]) labels ++
116 concatMap (\x -> ["and", "older-than", x]) minimumAge
117
118parseItem :: Text -> Either String BupItem
119parseItem = eitherDecode . encodeUtf8