[GHC] #16166: Compiling with profiling on Windows can cause linker errors
GHC
ghc-devs at haskell.org
Sat Jan 19 13:27:05 UTC 2019
#16166: Compiling with profiling on Windows can cause linker errors
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
Resolution: | Keywords:
Operating System: Windows | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* cc: Phyx- (added)
* status: closed => new
* resolution: invalid =>
Comment:
No need to file a `stack` bug, as your initial hunch was correct: this is
a GHC bug. You can reproduce this issue using nothing but GHC and your
repro case:
{{{#!hs
{-# LANGUAGE BangPatterns #-}
-- NetworkRequestHeader.hs
module NetworkRequestHeader (parseHeaderLines, parseRequestLine) where
import Control.Exception
import Control.Monad
import Data.ByteString.Internal (ByteString(..), memchr)
import Data.Word
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (Ptr, plusPtr, minusPtr, nullPtr)
import Foreign.Storable (peek)
-- | Error types for bad 'Request'.
data InvalidRequest = NonHttp
instance Show InvalidRequest where show _ = ""
instance Exception InvalidRequest
parseHeaderLines :: [ByteString]
-> IO (ByteString
,ByteString -- Path
,ByteString -- Path, parsed
)
parseHeaderLines [] = throwIO $ NonHttp
parseHeaderLines (firstLine:_) = do
(method, path') <- parseRequestLine firstLine
let path = path'
return (method, path', path)
parseRequestLine :: ByteString
-> IO (ByteString
,ByteString)
parseRequestLine (PS fptr off len) = withForeignPtr fptr $ \ptr -> do
when (len < 14) $ throwIO NonHttp
let methodptr = ptr `plusPtr` off
limptr = methodptr `plusPtr` len
lim0 = fromIntegral len
pathptr0 <- memchr methodptr 32 lim0 -- ' '
when (pathptr0 == nullPtr || (limptr `minusPtr` pathptr0) < 11) $
throwIO NonHttp
let pathptr = pathptr0 `plusPtr` 1
lim1 = fromIntegral (limptr `minusPtr` pathptr0)
httpptr0 <- memchr pathptr 32 lim1 -- ' '
when (httpptr0 == nullPtr || (limptr `minusPtr` httpptr0) < 9) $
throwIO NonHttp
let httpptr = httpptr0 `plusPtr` 1
lim2 = fromIntegral (httpptr0 `minusPtr` pathptr)
checkHTTP httpptr
queryptr <- memchr pathptr 63 lim2 -- '?'
let !method = bs ptr methodptr pathptr0
!path
| queryptr == nullPtr = bs ptr pathptr httpptr0
| otherwise = bs ptr pathptr queryptr
return (method,path)
where
check :: Ptr Word8 -> Int -> Word8 -> IO ()
check p n w = do
w0 <- peek $ p `plusPtr` n
when (w0 /= w) $ throwIO NonHttp
checkHTTP httpptr = do
check httpptr 0 72 -- 'H'
check httpptr 1 84 -- 'T'
check httpptr 2 84 -- 'T'
check httpptr 3 80 -- 'P'
check httpptr 4 47 -- '/'
check httpptr 6 46 -- '.'
bs ptr p0 p1 = PS fptr o l
where
o = p0 `minusPtr` ptr
l = p1 `minusPtr` p0
}}}
{{{#!hs
$ more Main.hs
{-# LANGUAGE BangPatterns #-}
-- Main.hs
module Main (main) where
import Network.RequestHeader
import Control.Monad
main :: IO ()
main = void $ parseHeaderLines []
}}}
{{{
$ ghc -O1 -fforce-recomp -prof -fprof-auto Main.hs
[1 of 2] Compiling Network.RequestHeader ( Network\RequestHeader.hs,
Network\RequestHeader.o )
[2 of 2] Compiling Main ( Main.hs, Main.o )
Linking Main.exe ...
.\Network\RequestHeader.o:fake:(.text+0x920): undefined reference to
`__chkstk_ms'
.\Network\RequestHeader.o:fake:(.text+0xc10): undefined reference to
`__chkstk_ms'
.\Network\RequestHeader.o:fake:(.text+0xc70): undefined reference to
`__chkstk_ms'
.\Network\RequestHeader.o:fake:(.text+0xdd8): undefined reference to
`__chkstk_ms'
.\Network\RequestHeader.o:fake:(.text+0xe90): undefined reference to
`__chkstk_ms'
.\Network\RequestHeader.o:fake:(.text+0xee0): more undefined references to
`__chkstk_ms' follow
collect2.exe: error: ld returned 1 exit status
`gcc.exe' failed in phase `Linker'. (Exit code: 1)
}}}
Note that both the `-O1` and `-fprof-auto` flags are required to trigger
the linker errors. (This explains why you seemingly couldn't trigger the
error with `cabal-install`, as `cabal-install`'s `--enable-profiling`
option doesn't imply the `-fprof-auto` flag, whereas `stack`'s `--profile`
option does.)
Phyx-, any ideas as to what might be causing this?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16166#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list