mirror of
https://github.com/commercialhaskell/stackage-server.git
synced 2026-01-12 04:08:29 +01:00
Merge pull request #316 from ysangkok/master
Compatibility with newer dependencies
This commit is contained in:
commit
1638873d8d
@ -11,6 +11,9 @@ module Settings where
|
||||
|
||||
import ClassyPrelude.Yesod
|
||||
import Data.Aeson (Result(..), fromJSON, withObject, (.!=), (.:?))
|
||||
#if MIN_VERSION_aeson(2,0,0)
|
||||
import Data.Aeson.KeyMap (KeyMap)
|
||||
#endif
|
||||
import Data.FileEmbed (embedFile)
|
||||
import Data.Yaml (decodeEither', Parser)
|
||||
import Data.Yaml.Config
|
||||
@ -61,7 +64,11 @@ data DatabaseSettings
|
||||
|
||||
parseDatabase
|
||||
:: Bool -- ^ is this dev? if so, allow default of SQLite
|
||||
#if MIN_VERSION_aeson(2,0,0)
|
||||
-> KeyMap Value
|
||||
#else
|
||||
-> HashMap Text Value
|
||||
#endif
|
||||
-> Parser DatabaseSettings
|
||||
parseDatabase isDev o =
|
||||
if isDev
|
||||
|
||||
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
module Stackage.Database.Haddock
|
||||
( renderHaddock
|
||||
@ -8,6 +9,9 @@ import qualified Documentation.Haddock.Parser as Haddock
|
||||
import Documentation.Haddock.Types (DocH(..), Example(..), Header(..),
|
||||
Hyperlink(..), MetaDoc(..), Picture(..),
|
||||
Table(..), TableCell(..), TableRow(..))
|
||||
#if MIN_VERSION_haddock_library(1,10,0)
|
||||
import Documentation.Haddock.Types (ModLink(modLinkName))
|
||||
#endif
|
||||
import Text.Blaze.Html (Html, toHtml)
|
||||
import qualified Text.Blaze.Html5 as H
|
||||
import qualified Text.Blaze.Html5.Attributes as A
|
||||
@ -27,13 +31,21 @@ hToHtml =
|
||||
go (DocParagraph x) = H.p $ go x
|
||||
go (DocIdentifier s) = H.code $ toHtml s
|
||||
go (DocIdentifierUnchecked s) = H.code $ toHtml s
|
||||
#if MIN_VERSION_haddock_library(1,10,0)
|
||||
go (DocModule modLink) = H.code $ toHtml $ modLinkName modLink
|
||||
#else
|
||||
go (DocModule s) = H.code $ toHtml s
|
||||
#endif
|
||||
go (DocWarning x) = H.span H.! A.class_ "warning" $ go x
|
||||
go (DocEmphasis x) = H.em $ go x
|
||||
go (DocMonospaced x) = H.code $ go x
|
||||
go (DocBold x) = H.strong $ go x
|
||||
go (DocUnorderedList xs) = H.ul $ foldMap (H.li . go) xs
|
||||
#if MIN_VERSION_haddock_library(1,11,0)
|
||||
go (DocOrderedList xs) = H.ol $ foldMap (H.li . go . snd) xs
|
||||
#else
|
||||
go (DocOrderedList xs) = H.ol $ foldMap (H.li . go) xs
|
||||
#endif
|
||||
go (DocDefList xs) = H.dl $ flip foldMap xs $ \(x, y) ->
|
||||
H.dt (go x) ++ H.dd (go y)
|
||||
go (DocCodeBlock x) = H.pre $ H.code $ go x
|
||||
|
||||
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DerivingStrategies #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
@ -46,7 +47,12 @@ module Stackage.Database.Schema
|
||||
, module PS
|
||||
) where
|
||||
|
||||
import Control.Monad.Logger (runNoLoggingT, runStdoutLoggingT, MonadLogger)
|
||||
import Control.Monad.Logger (runNoLoggingT, runStdoutLoggingT)
|
||||
#if MIN_VERSION_monad_logger(0,3,10) && MIN_VERSION_persistent_postgresql(2,12,0)
|
||||
import Control.Monad.Logger (MonadLoggerIO)
|
||||
#else
|
||||
import Control.Monad.Logger (MonadLogger)
|
||||
#endif
|
||||
import qualified Data.Aeson as A
|
||||
import Data.Pool (destroyAllResources, Pool)
|
||||
import Database.Persist
|
||||
@ -186,7 +192,12 @@ run inner = do
|
||||
|
||||
withStackageDatabase :: MonadUnliftIO m => Bool -> DatabaseSettings -> (StackageDatabase -> m a) -> m a
|
||||
withStackageDatabase shouldLog dbs inner = do
|
||||
let makePool :: (MonadUnliftIO m, MonadLogger m) => m (Pool SqlBackend)
|
||||
let
|
||||
#if MIN_VERSION_monad_logger(0,3,10) && MIN_VERSION_persistent_postgresql(2,12,0)
|
||||
makePool :: (MonadUnliftIO m, MonadLoggerIO m) => m (Pool SqlBackend)
|
||||
#else
|
||||
makePool :: (MonadUnliftIO m, MonadLogger m) => m (Pool SqlBackend)
|
||||
#endif
|
||||
makePool =
|
||||
case dbs of
|
||||
DSPostgres connStr mSize -> do
|
||||
|
||||
Loading…
Reference in New Issue
Block a user