3
3
{-# LANGUAGE TemplateHaskell #-}
4
4
{-# LANGUAGE TypeFamilies #-}
5
5
{-# LANGUAGE DerivingStrategies #-}
6
- module Distribution.Server.Features.Vouch where
6
+ module Distribution.Server.Features.Vouch ( VouchError ( .. ), VouchSuccess ( .. ), initVouchFeature , judgeVouch ) where
7
7
8
8
import Control.Monad (when , join )
9
9
import Control.Monad.Except (runExceptT , throwError )
@@ -91,23 +91,32 @@ instance IsHackageFeature VouchFeature where
91
91
getFeatureInterface = vouchFeatureInterface
92
92
93
93
requiredCountOfVouches :: Int
94
- requiredCountOfVouches = 3
94
+ requiredCountOfVouches = 2
95
95
96
96
isWithinLastMonth :: UTCTime -> (UserId , UTCTime ) -> Bool
97
97
isWithinLastMonth now (_, vouchTime) =
98
- addUTCTime (30 * nominalDay) vouchTime < now
98
+ addUTCTime (30 * nominalDay) vouchTime >= now
99
99
100
- data Err
100
+ data VouchError
101
101
= NotAnUploader
102
102
| You'reTooNew
103
103
| VoucheeAlreadyUploader
104
104
| AlreadySufficientlyVouched
105
105
| YouAlreadyVouched
106
-
107
- data Success = AddVouchComplete | AddVouchIncomplete
108
-
109
- judge :: Group. UserIdSet -> UTCTime -> UserId -> [(UserId , UTCTime )] -> [(UserId , UTCTime )] -> UserId -> Either Err (Either Err Success )
110
- judge ugroup now vouchee vouchersForVoucher existingVouchers voucher = runExceptT $ do
106
+ deriving stock (Show , Eq )
107
+
108
+ data VouchSuccess = AddVouchComplete | AddVouchIncomplete Int
109
+ deriving stock (Show , Eq )
110
+
111
+ judgeVouch
112
+ :: Group. UserIdSet
113
+ -> UTCTime
114
+ -> UserId
115
+ -> [(UserId , UTCTime )]
116
+ -> [(UserId , UTCTime )]
117
+ -> UserId
118
+ -> Either VouchError VouchSuccess
119
+ judgeVouch ugroup now vouchee vouchersForVoucher existingVouchers voucher = join . runExceptT $ do
111
120
when (not (voucher `Group.member` ugroup)) $
112
121
throwError NotAnUploader
113
122
-- You can only vouch for non-uploaders, so if this list has items, the user is uploader because of these vouches.
@@ -116,33 +125,35 @@ judge ugroup now vouchee vouchersForVoucher existingVouchers voucher = runExcept
116
125
throwError You'reTooNew
117
126
when (vouchee `Group.member` ugroup) $
118
127
throwError VoucheeAlreadyUploader
119
- when (length existingVouchers >= 3 ) $
128
+ when (length existingVouchers >= requiredCountOfVouches ) $
120
129
throwError AlreadySufficientlyVouched
121
130
when (voucher `elem` map fst existingVouchers) $
122
131
throwError YouAlreadyVouched
123
132
pure $
124
133
if length existingVouchers == requiredCountOfVouches - 1
125
134
then AddVouchComplete
126
- else AddVouchIncomplete
135
+ else
136
+ let stillRequired = requiredCountOfVouches - length existingVouchers - 1
137
+ in AddVouchIncomplete stillRequired
127
138
128
139
renderToLBS :: (UserId -> ServerPartE UserInfo ) -> [(UserId , UTCTime )] -> ServerPartE TemplateAttr
129
140
renderToLBS lookupUserInfo vouches = do
130
- rendered <- traverse renderVouchers vouches
141
+ rendered <- traverse ( renderVouchers lookupUserInfo) vouches
131
142
pure $
132
143
templateUnescaped " vouches" $
133
144
if null rendered
134
145
then LBS. pack " Nobody has vouched yet."
135
146
else LBS. intercalate mempty rendered
136
- where
137
- renderVouchers :: (UserId , UTCTime ) -> ServerPartE LBS. ByteString
138
- renderVouchers (uid, timestamp) = do
139
- info <- lookupUserInfo uid
140
- let UserName name = userName info
141
- -- We don't need to show millisecond precision
142
- -- So we truncate it off here
143
- truncated = truncate $ utctDayTime timestamp
144
- newUTCTime = timestamp {utctDayTime = secondsToDiffTime truncated}
145
- pure . toUTF8LBS . prettyHtmlFragment . li . stringToHtml $ name <> " vouched on " <> formatShow iso8601Format newUTCTime
147
+
148
+ renderVouchers :: ( UserId -> ServerPartE UserInfo ) -> (UserId , UTCTime ) -> ServerPartE LBS. ByteString
149
+ renderVouchers lookupUserInfo (uid, timestamp) = do
150
+ info <- lookupUserInfo uid
151
+ let UserName name = userName info
152
+ -- We don't need to show millisecond precision
153
+ -- So we truncate it off here
154
+ truncated = truncate $ utctDayTime timestamp
155
+ newUTCTime = timestamp {utctDayTime = secondsToDiffTime truncated}
156
+ pure . toUTF8LBS . prettyHtmlFragment . li . stringToHtml $ name <> " vouched on " <> formatShow iso8601Format newUTCTime
146
157
147
158
initVouchFeature :: ServerEnv -> IO (UserFeature -> UploadFeature -> IO VouchFeature )
148
159
initVouchFeature ServerEnv {serverStateDir, serverTemplatesDir, serverTemplatesMode} = do
@@ -170,7 +181,7 @@ initVouchFeature ServerEnv{serverStateDir, serverTemplatesDir, serverTemplatesMo
170
181
vouchee <- lookupUserName =<< userNameInPath dpath
171
182
vouchersForVoucher <- queryState vouchState $ GetVouchesFor voucher
172
183
existingVouchers <- queryState vouchState $ GetVouchesFor vouchee
173
- case join $ judge ugroup now vouchee vouchersForVoucher existingVouchers voucher of
184
+ case judgeVouch ugroup now vouchee vouchersForVoucher existingVouchers voucher of
174
185
Left NotAnUploader ->
175
186
errBadRequest " Not an uploader" [MText " You must be an uploader yourself to vouch for other users." ]
176
187
Left You'reTooNew ->
@@ -191,8 +202,7 @@ initVouchFeature ServerEnv{serverStateDir, serverTemplatesDir, serverTemplatesMo
191
202
[ " msg" $= " Added vouch. User is now an uploader!"
192
203
, param
193
204
]
194
- AddVouchIncomplete -> do
195
- let stillRequired = requiredCountOfVouches - length existingVouchers - 1
205
+ AddVouchIncomplete stillRequired ->
196
206
pure . toResponse $ vouchTemplate
197
207
[ " msg" $=
198
208
" Added vouch. User still needs "
0 commit comments