mirror of
https://github.com/commercialhaskell/stackage-server.git
synced 2026-01-15 21:58:29 +01:00
LTS bump
This commit is contained in:
parent
ade312b9df
commit
a030ba4afb
@ -5,7 +5,7 @@ module Application
|
|||||||
, makeFoundation
|
, makeFoundation
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Concurrent (forkIO, threadDelay)
|
import Control.Concurrent (forkIO)
|
||||||
import Control.Exception (catch)
|
import Control.Exception (catch)
|
||||||
import Data.WebsiteContent
|
import Data.WebsiteContent
|
||||||
import Import hiding (catch)
|
import Import hiding (catch)
|
||||||
|
|||||||
@ -1,39 +0,0 @@
|
|||||||
module Handler.BannedTags where
|
|
||||||
|
|
||||||
import Data.Slug (unSlug, Slug)
|
|
||||||
import Data.Tag
|
|
||||||
import Import
|
|
||||||
|
|
||||||
checkSlugs :: Monad m => Textarea -> m (Either Text [Slug])
|
|
||||||
checkSlugs (Textarea t) =
|
|
||||||
return $ first tshow $ (mapM mkTag $ filter (not . null) $ lines $ filter (/= '\r') t)
|
|
||||||
|
|
||||||
fromSlugs :: [Slug] -> Textarea
|
|
||||||
fromSlugs = Textarea . unlines . map unSlug
|
|
||||||
|
|
||||||
getBannedTagsR :: Handler Html
|
|
||||||
getBannedTagsR = do
|
|
||||||
Entity _ user <- requireAuth
|
|
||||||
extra <- getExtra
|
|
||||||
when (unSlug (userHandle user) `notMember` adminUsers extra)
|
|
||||||
$ permissionDenied "You are not an administrator"
|
|
||||||
curr <- fmap (map (bannedTagTag . entityVal))
|
|
||||||
$ runDB $ selectList [] [Asc BannedTagTag]
|
|
||||||
((res, widget), enctype) <- runFormPost $ renderDivs
|
|
||||||
$ fmap (fromMaybe [])
|
|
||||||
$ aopt
|
|
||||||
(checkMMap checkSlugs fromSlugs textareaField)
|
|
||||||
"Banned tags (one per line)" $ Just (Just curr)
|
|
||||||
case res of
|
|
||||||
FormSuccess tags -> do
|
|
||||||
runDB $ do
|
|
||||||
deleteWhere ([] :: [Filter BannedTag])
|
|
||||||
insertMany_ $ map BannedTag tags
|
|
||||||
setMessage "Tags updated"
|
|
||||||
redirect BannedTagsR
|
|
||||||
_ -> defaultLayout $ do
|
|
||||||
setTitle "Banned Tags"
|
|
||||||
$(widgetFile "banned-tags")
|
|
||||||
|
|
||||||
putBannedTagsR :: Handler Html
|
|
||||||
putBannedTagsR = getBannedTagsR
|
|
||||||
@ -5,7 +5,6 @@ module Stackage.Database.Cron
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import ClassyPrelude.Conduit
|
import ClassyPrelude.Conduit
|
||||||
import Control.Concurrent (threadDelay)
|
|
||||||
import Stackage.PackageIndex.Conduit
|
import Stackage.PackageIndex.Conduit
|
||||||
import Database.Persist (Entity (Entity))
|
import Database.Persist (Entity (Entity))
|
||||||
import Data.Char (isAlpha)
|
import Data.Char (isAlpha)
|
||||||
|
|||||||
@ -1,4 +1,4 @@
|
|||||||
resolver: lts-5.1
|
resolver: lts-5.15
|
||||||
image:
|
image:
|
||||||
container:
|
container:
|
||||||
name: fpco/stackage-server
|
name: fpco/stackage-server
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user