Skip to content

Commit b46b3c7

Browse files
committed
Conditional compilation for signal handling
Will not compile on windows
1 parent 079cf0a commit b46b3c7

File tree

2 files changed

+12
-4
lines changed

2 files changed

+12
-4
lines changed

postgrest.cabal

+2-1
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,8 @@ executable postgrest
6161
, HTTP, http-types
6262
, MissingH
6363
, Ranged-sets
64-
, unix >= 2.7 && < 3
64+
if !os(windows)
65+
build-depends: unix >= 2.7 && < 3
6566

6667
hs-source-dirs: src
6768
other-modules: Paths_postgrest

src/PostgREST/Main.hs

+10-3
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE CPP #-}
2+
13
module Main where
24

35

@@ -10,8 +12,6 @@ import PostgREST.DbStructure
1012
import PostgREST.Error (PgError, pgErrResponse)
1113
import PostgREST.Middleware
1214

13-
import Control.Concurrent (myThreadId)
14-
import Control.Exception.Base (throwTo, AsyncException(..))
1515
import Control.Monad (unless, void)
1616
import Control.Monad.IO.Class (liftIO)
1717
import Data.Aeson (encode)
@@ -28,9 +28,14 @@ import Network.Wai.Middleware.RequestLogger (logStdout)
2828
import System.IO (BufferMode (..),
2929
hSetBuffering, stderr,
3030
stdin, stdout)
31-
import System.Posix.Signals
3231
import Web.JWT (secret)
3332

33+
#ifndef mingw32_HOST_OS
34+
import System.Posix.Signals
35+
import Control.Concurrent (myThreadId)
36+
import Control.Exception.Base (throwTo, AsyncException(..))
37+
#endif
38+
3439
isServerVersionSupported :: H.Session P.Postgres IO Bool
3540
isServerVersionSupported = do
3641
Identity (row :: Text) <- H.tx Nothing $ H.singleEx [H.stmt|SHOW server_version_num|]
@@ -72,11 +77,13 @@ main = do
7277
<> show minimumPgVersion)
7378
) supportedOrError
7479

80+
#ifndef mingw32_HOST_OS
7581
tid <- myThreadId
7682
void $ installHandler keyboardSignal (Catch $ do
7783
H.releasePool pool
7884
throwTo tid UserInterrupt
7985
) Nothing
86+
#endif
8087

8188
let txSettings = Just (H.ReadCommitted, Just True)
8289
dbOrError <- H.session pool $ H.tx txSettings $ getDbStructure (cs $ configSchema conf)

0 commit comments

Comments
 (0)