aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorYuchen Pei <hi@ypei.me>2022-06-13 15:33:06 +1000
committerYuchen Pei <hi@ypei.me>2022-06-13 15:33:06 +1000
commit8793dfc66dcab759a95e4f6ab98e07afbc45784b (patch)
treecd3f21b53cb9184c62140cd56bfc729311ae5b4e
parent84183f26a358ec89fdcaa5b9f50271566d5999b6 (diff)
removing cpp macros in server
-rw-r--r--app/Server.hs19
1 files changed, 0 insertions, 19 deletions
diff --git a/app/Server.hs b/app/Server.hs
index c220307..e67e21f 100644
--- a/app/Server.hs
+++ b/app/Server.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TupleSections #-}
@@ -51,9 +50,7 @@ import qualified Data.List as L
import qualified Data.Map.Strict as M
import Data.Maybe (fromMaybe, mapMaybe)
import qualified Data.Vector as V
-#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
import qualified GHC.Compact as C
-#endif
import Data.Pagination
( Paginated
, hasNextPage
@@ -125,11 +122,7 @@ import Servant
, Header
, Headers
, QueryParam
-#if MIN_VERSION_GLASGOW_HASKELL(8,6,5,0)
, ServerError
-#else
- , ServantErr
-#endif
, ServerT
, ToHttpApiData(..)
, addHeader
@@ -141,11 +134,7 @@ import Servant
)
import Servant.API.ContentTypes (AllCTRender(..), JSON)
import Servant.Server (Handler(..), hoistServer)
-#if MIN_VERSION_servant(0,14,1)
import Servant.Links (safeLink)
-#else
-import Servant.Utils.Links (safeLink)
-#endif
import System.Directory (doesFileExist)
import System.Exit (exitFailure, exitSuccess)
import System.FilePath.Find
@@ -882,11 +871,7 @@ isExportedId (HCE.ExternalIdentifierInfo HCE.IdentifierInfo {isExported}) =
ghcCompact :: forall a. a -> IO a
ghcCompact =
-#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
(fmap C.getCompact . C.compact)
-#else
- return
-#endif
loadPackageInfo ::
ServerConfig
@@ -1839,11 +1824,7 @@ fileNotFound :: Response
fileNotFound =
responseLBS status404 [("Content-Type", "text/plain")] "Not found"
-#if MIN_VERSION_GLASGOW_HASKELL(8,6,5,0)
throwServantError :: (MonadIO m) => ServerError -> m a
-#else
-throwServantError :: (MonadIO m) => ServantErr -> m a
-#endif
throwServantError = liftIO . throwIO
server :: Environment -> ServerT API Handler