Skip to content
Snippets Groups Projects
Commit 3b96c7f8 authored by Ryan Scott's avatar Ryan Scott
Browse files

Merge branch 'blaze-textual' into 'master'

Add blaze-textual patch

See merge request ghc/head.hackage!165
parents e805210c 19f88cec
No related branches found
No related tags found
No related merge requests found
diff --git a/Blaze/Text/Int.hs b/Blaze/Text/Int.hs
index 58cdbf4..2e8809d 100644
--- a/Blaze/Text/Int.hs
+++ b/Blaze/Text/Int.hs
@@ -27,7 +27,7 @@ import GHC.Num (quotRemInteger)
import GHC.Types (Int(..))
#if defined(INTEGER_GMP)
-import GHC.Integer.GMP.Internals
+import GHC.Integer.GMP.Internals hiding (quotRemInteger)
#elif defined(INTEGER_SIMPLE)
import GHC.Integer.Simple.Internals
#endif
File moved
diff --git a/src/Servant/API/ContentTypes.hs b/src/Servant/API/ContentTypes.hs
index d6d200a..b860970 100644
index 1706a04..10e8d89 100644
--- a/src/Servant/API/ContentTypes.hs
+++ b/src/Servant/API/ContentTypes.hs
@@ -2,6 +2,7 @@
......@@ -10,13 +10,3 @@ index d6d200a..b860970 100644
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
diff --git a/src/Servant/API/UVerb/Union.hs b/src/Servant/API/UVerb/Union.hs
index 1b77621..8f42138 100644
--- a/src/Servant/API/UVerb/Union.hs
+++ b/src/Servant/API/UVerb/Union.hs
@@ -144,4 +144,4 @@ _testNubbed :: ( ( Nubbed '[Bool, Int, Int] ~ 'False
, Nubbed '[Int, Bool] ~ 'True
)
=> a) -> a
-_testNubbed = id
+_testNubbed x = x
......@@ -51,8 +51,37 @@ index 25cf498..2783c2e 100644
where
!(Table addr) = table
table :: Table
diff --git a/Network/Wai/Handler/Warp/Settings.hs b/Network/Wai/Handler/Warp/Settings.hs
index 7c4dd03..955e207 100644
--- a/Network/Wai/Handler/Warp/Settings.hs
+++ b/Network/Wai/Handler/Warp/Settings.hs
@@ -28,6 +28,10 @@ import System.TimeManager
import Network.Wai.Handler.Warp.Imports
import Network.Wai.Handler.Warp.Types
+#if __GLASGOW_HASKELL__ >= 903
+import GHC.IO (unIO)
+#endif
+
-- | Various Warp server settings. This is purposely kept as an abstract data
-- type so that new settings can be added without breaking backwards
-- compatibility. In order to create a 'Settings' value, use 'defaultSettings'
@@ -250,6 +254,12 @@ exceptionResponseForDebug e =
defaultFork :: ((forall a. IO a -> IO a) -> IO ()) -> IO ()
defaultFork io =
IO $ \s0 ->
- case (fork# (io unsafeUnmask) s0) of
+ case (fork#
+#if __GLASGOW_HASKELL__ >= 903
+ (unIO (io unsafeUnmask))
+#else
+ (io unsafeUnmask)
+#endif
+ s0) of
(# s1, _tid #) ->
(# s1, () #)
diff --git a/warp.cabal b/warp.cabal
index 0f52494..dc012a8 100644
index 7d7ca12..adee1e2 100644
--- a/warp.cabal
+++ b/warp.cabal
@@ -74,6 +74,7 @@ Library
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment