[GHC] #12974: Solution to regular expression is no longer valid

#12974: Solution to regular expression is no longer valid -------------------------------------+------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following HUnit test code {{{#!hs module Main where import Test.HUnit import Text.Regex.Posix testRegexSimple :: Test testRegexSimple = TestCase $ do assertBool "pattern matches regex ^(a)|(p)$" ( "p" =~ "^(a)|(p)$" ) testRegex :: Test testRegex = TestCase $ do assertBool "pattern matches regex ^(ab+c*d?)|(ef{2}g{3,6}h{3,})|(p)$" ( "p" =~ "^(ab+c*d?)|(ef{2}g{3,6}h{3,})|(p)$" ) tests = TestList [ TestLabel "Regex Simple" testRegexSimple, TestLabel "Regex" testRegex ] main :: IO Counts main = do runTestTT tests }}} runs perfectly using Haskell platform 2013.2.0.0 with ghc 7.6.3. However, on stack LTS 7.13 with ghc 8.0.1 the second test fails! I assume this behaviour is the result of a bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+---------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by pjljvdlaar): * keywords: => regex * os: Unknown/Multiple => Windows -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by pjljvdlaar): * architecture: Unknown/Multiple => x86_64 (amd64) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by mpickering): Is this a bug in GHC or a bug in the regular expression library? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by rwbarton): Hard to imagine it could be a GHC bug. However Haskell platform 2013.2.0.0 and LTS 7.13 both have the same version regex-posix 0.95.2 and on Windows the regex engine even appears to be bundled as C source within the Cabal package... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by bgamari): To install the dependencies required for this test, {{{ $ cabal install hunit regex-posix }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by bgamari): Hmm, I am unable to reproduce this on x86_64 Linux with GHC 8.0.1, `HUnit-1.5.0.0`, and `regex-posix-0.95.2`. Trying Windows next. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by bgamari): Hmm, interesting. Indeed this is reproducible with the same versions on Windows. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by rwbarton): Not too surprising that it is Windows-specific if you look at the regex- posix.cabal file (it uses bundled sources on Windows only). But the GHC version dependence is a mystery. Perhaps it could be the string literal inlining issue, #12757? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by pjljvdlaar): Issue still present in GHC 8.0.2 on windows. Tested with LTS 8.5 - https://www.stackage.org/lts-8.5 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by ezyang): We have also noticed that regex-posix is buggy on Windows, but I'm pretty sure this is a regex-posix/underlying library problem than a GHC problem. See also https://github.com/haskell/cabal/issues/4336 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by RyanGlScott): The issue isn't GHC 7.6.3 vs. 8.0.2. Rather, it's a 32-bit vs. 64-bit Windows GHC difference. I tested the program on GHC 7.10.2, 7.10.3, and 8.0.2 using both the 32-bit and 64-bit versions, and the 32-bit versions all succeeded whereas the 64-bit versions all failed the second test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by RyanGlScott): Since I was curious to learn //how// the second test was failing, I cooked up a slight variant of the program: {{{#!hs {-# LANGUAGE PackageImports #-} module Main (main) where import "regex-compat" Text.Regex main :: IO () main = do print $ matchRegexAll (mkRegex "^(a)|(p)$") "p" print $ matchRegexAll (mkRegex "^(ab+c*d?)|(ef{2}g{3,6}h{3,})|(p)$") "p" }}} This requires the `regex-compat` package (a thin shim on top of `regex- posix`). With 32-bit Windows GHC, running this program gives you: {{{ Just ("","p","",[]) Just ("","p","",[]) }}} With 64-bit Windows GHC: {{{ Just ("","p","",["","p"]) Nothing }}} With 64-bit Linux GHC: {{{ Just ("","p","",["","p"]) Just ("","p","",["","","p"]) }}} The most likely culprits are the C files (`regex.h` and friends) that are shipped with `regex-posix`, as they're most likely quite old. I'll see if I can find a more up-to-date version. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12974: Solution to regular expression is no longer valid ---------------------------------+-------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: invalid | Keywords: regex Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => invalid Comment: Since the issue appears to be specific to `regex-posix`, I'm going to close this. Moreover, as ezyang notes in https://github.com/haskell/cabal/issues/4336, the `regex-tdfa` library serves as a drop-in replacement for `regex-posix` which //does// pass both of those tests on 64-bit Windows. (I've also verified that `regex-pcre` works as well.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12974#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC