Skip to content

Commit

Permalink
Conditional compilation for signal handling
Browse files Browse the repository at this point in the history
Will not compile on windows
  • Loading branch information
begriffs committed Dec 17, 2015
1 parent 079cf0a commit b46b3c7
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 4 deletions.
3 changes: 2 additions & 1 deletion postgrest.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,8 @@ executable postgrest
, HTTP, http-types
, MissingH
, Ranged-sets
, unix >= 2.7 && < 3
if !os(windows)
build-depends: unix >= 2.7 && < 3

hs-source-dirs: src
other-modules: Paths_postgrest
Expand Down
13 changes: 10 additions & 3 deletions src/PostgREST/Main.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE CPP #-}

module Main where


Expand All @@ -10,8 +12,6 @@ import PostgREST.DbStructure
import PostgREST.Error (PgError, pgErrResponse)
import PostgREST.Middleware

import Control.Concurrent (myThreadId)
import Control.Exception.Base (throwTo, AsyncException(..))
import Control.Monad (unless, void)
import Control.Monad.IO.Class (liftIO)
import Data.Aeson (encode)
Expand All @@ -28,9 +28,14 @@ import Network.Wai.Middleware.RequestLogger (logStdout)
import System.IO (BufferMode (..),
hSetBuffering, stderr,
stdin, stdout)
import System.Posix.Signals
import Web.JWT (secret)

#ifndef mingw32_HOST_OS
import System.Posix.Signals
import Control.Concurrent (myThreadId)
import Control.Exception.Base (throwTo, AsyncException(..))
#endif

isServerVersionSupported :: H.Session P.Postgres IO Bool
isServerVersionSupported = do
Identity (row :: Text) <- H.tx Nothing $ H.singleEx [H.stmt|SHOW server_version_num|]
Expand Down Expand Up @@ -72,11 +77,13 @@ main = do
<> show minimumPgVersion)
) supportedOrError

#ifndef mingw32_HOST_OS
tid <- myThreadId
void $ installHandler keyboardSignal (Catch $ do
H.releasePool pool
throwTo tid UserInterrupt
) Nothing
#endif

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

0 comments on commit b46b3c7

Please sign in to comment.