3
3
{-# LANGUAGE TemplateHaskell #-}
4
4
{-# LANGUAGE TypeFamilies #-}
5
5
{-# LANGUAGE DerivingStrategies #-}
6
- module Distribution.Server.Features.Vouch (VouchError (.. ), VouchSuccess (.. ), initVouchFeature , judgeVouch ) where
6
+ {-# LANGUAGE RankNTypes #-}
7
+ module Distribution.Server.Features.Vouch (VouchFeature (.. ), VouchData (.. ), VouchError (.. ), VouchSuccess (.. ), initVouchFeature , judgeVouch ) where
7
8
8
9
import Control.Monad (when , join )
9
10
import Control.Monad.Except (runExceptT , throwError )
10
11
import Control.Monad.Reader (ask )
11
12
import Control.Monad.State (get , put )
13
+ import Control.Monad.IO.Class (MonadIO )
12
14
import qualified Data.ByteString.Lazy.Char8 as LBS
13
15
import qualified Data.Map.Strict as Map
16
+ import qualified Data.Set as Set
14
17
import Data.Maybe (fromMaybe )
15
18
import Data.Time (UTCTime (.. ), addUTCTime , getCurrentTime , nominalDay , secondsToDiffTime )
16
19
import Data.Time.Format.ISO8601 (formatShow , iso8601Format )
17
20
import Text.XHtml.Strict (prettyHtmlFragment , stringToHtml , li )
18
21
19
22
import Data.SafeCopy (base , deriveSafeCopy )
20
- import Distribution.Server.Framework ((</>) , AcidState , DynamicPath , HackageFeature , IsHackageFeature , IsHackageFeature (.. ), MemSize )
23
+ import Distribution.Server.Framework ((</>) , AcidState , DynamicPath , HackageFeature , IsHackageFeature , IsHackageFeature (.. ), MemSize ( .. ), memSize2 )
21
24
import Distribution.Server.Framework (MessageSpan (MText ), Method (.. ), Query , Response , ServerEnv (.. ), ServerPartE , StateComponent (.. ), Update )
22
25
import Distribution.Server.Framework (abstractAcidStateComponent , emptyHackageFeature , errBadRequest )
23
26
import Distribution.Server.Framework (featureDesc , featureReloadFiles , featureResources , featureState )
@@ -31,20 +34,26 @@ import Distribution.Server.Features.Upload(UploadFeature(..))
31
34
import Distribution.Server.Features.Users (UserFeature (.. ))
32
35
import Distribution.Simple.Utils (toUTF8LBS )
33
36
34
- newtype VouchData = VouchData (Map. Map UserId [(UserId , UTCTime )])
37
+ data VouchData =
38
+ VouchData
39
+ { vouches :: Map. Map UserId [(UserId , UTCTime )]
40
+ , notNotified :: Set. Set UserId
41
+ }
35
42
deriving (Show , Eq )
36
- deriving newtype MemSize
43
+
44
+ instance MemSize VouchData where
45
+ memSize (VouchData vouches notified) = memSize2 vouches notified
37
46
38
47
putVouch :: UserId -> (UserId , UTCTime ) -> Update VouchData ()
39
48
putVouch vouchee (voucher, now) = do
40
- VouchData tbl <- get
49
+ VouchData tbl notNotified <- get
41
50
let oldMap = fromMaybe [] (Map. lookup vouchee tbl)
42
51
newMap = (voucher, now) : oldMap
43
- put $ VouchData (Map. insert vouchee newMap tbl)
52
+ put $ VouchData (Map. insert vouchee newMap tbl) notNotified
44
53
45
54
getVouchesFor :: UserId -> Query VouchData [(UserId , UTCTime )]
46
55
getVouchesFor needle = do
47
- VouchData tbl <- ask
56
+ VouchData tbl _notNotified <- ask
48
57
pure . fromMaybe [] $ Map. lookup needle tbl
49
58
50
59
getVouchesData :: Query VouchData VouchData
@@ -65,8 +74,8 @@ makeAcidic ''VouchData
65
74
66
75
vouchStateComponent :: FilePath -> IO (StateComponent AcidState VouchData )
67
76
vouchStateComponent stateDir = do
68
- st <- openLocalStateFrom (stateDir </> " db" </> " Vouch" ) (VouchData mempty )
69
- let initialVouchData = VouchData mempty
77
+ st <- openLocalStateFrom (stateDir </> " db" </> " Vouch" ) (VouchData mempty mempty )
78
+ let initialVouchData = VouchData mempty mempty
70
79
restore =
71
80
RestoreBackup
72
81
{ restoreEntry = error " Unexpected backup entry"
@@ -85,6 +94,7 @@ vouchStateComponent stateDir = do
85
94
data VouchFeature =
86
95
VouchFeature
87
96
{ vouchFeatureInterface :: HackageFeature
97
+ , drainQueuedNotifications :: forall m . MonadIO m => m [UserId ]
88
98
}
89
99
90
100
instance IsHackageFeature VouchFeature where
@@ -167,8 +177,8 @@ initVouchFeature ServerEnv{serverStateDir, serverTemplatesDir, serverTemplatesMo
167
177
handleGetVouches :: DynamicPath -> ServerPartE Response
168
178
handleGetVouches dpath = do
169
179
uid <- lookupUserName =<< userNameInPath dpath
170
- userIds <- queryState vouchState $ GetVouchesFor uid
171
- param <- renderToLBS lookupUserInfo userIds
180
+ vouches <- queryState vouchState $ GetVouchesFor uid
181
+ param <- renderToLBS lookupUserInfo vouches
172
182
pure . toResponse $ vouchTemplate
173
183
[ " msg" $= " "
174
184
, param
@@ -197,6 +207,13 @@ initVouchFeature ServerEnv{serverStateDir, serverTemplatesDir, serverTemplatesMo
197
207
param <- renderToLBS lookupUserInfo $ existingVouchers ++ [(voucher, now)]
198
208
case result of
199
209
AddVouchComplete -> do
210
+ -- enqueue vouching completed notification
211
+ -- which will be read using drainQueuedNotifications
212
+ VouchData vouches notNotified <-
213
+ queryState vouchState GetVouchesData
214
+ let newState = VouchData vouches (Set. insert vouchee notNotified)
215
+ updateState vouchState $ ReplaceVouchesData newState
216
+
200
217
liftIO $ Group. addUserToGroup uploadersGroup vouchee
201
218
pure . toResponse $ vouchTemplate
202
219
[ " msg" $= " Added vouch. User is now an uploader!"
@@ -211,18 +228,26 @@ initVouchFeature ServerEnv{serverStateDir, serverTemplatesDir, serverTemplatesMo
211
228
<> " to become uploader."
212
229
, param
213
230
]
214
- return $ VouchFeature $
215
- (emptyHackageFeature " vouch" )
216
- { featureDesc = " Vouching for users getting upload permission."
217
- , featureResources =
218
- [(resourceAt " /user/:username/vouch" )
219
- { resourceDesc = [(GET , " list people vouching" )
220
- ,(POST , " vouch for user" )
221
- ]
222
- , resourceGet = [(" html" , handleGetVouches)]
223
- , resourcePost = [(" html" , handlePostVouch)]
224
- }
225
- ]
226
- , featureState = [ abstractAcidStateComponent vouchState ]
227
- , featureReloadFiles = reloadTemplates templates
228
- }
231
+ return $ VouchFeature {
232
+ vouchFeatureInterface =
233
+ (emptyHackageFeature " vouch" )
234
+ { featureDesc = " Vouching for users getting upload permission."
235
+ , featureResources =
236
+ [(resourceAt " /user/:username/vouch" )
237
+ { resourceDesc = [(GET , " list people vouching" )
238
+ ,(POST , " vouch for user" )
239
+ ]
240
+ , resourceGet = [(" html" , handleGetVouches)]
241
+ , resourcePost = [(" html" , handlePostVouch)]
242
+ }
243
+ ]
244
+ , featureState = [ abstractAcidStateComponent vouchState ]
245
+ , featureReloadFiles = reloadTemplates templates
246
+ },
247
+ drainQueuedNotifications = do
248
+ VouchData vouches notNotified <-
249
+ queryState vouchState GetVouchesData
250
+ let newState = VouchData vouches mempty
251
+ updateState vouchState $ ReplaceVouchesData newState
252
+ pure $ Set. toList notNotified
253
+ }
0 commit comments