[GHC] #9275: Missing import statement in GHC.Event.Poll
 
            #9275: Missing import statement in GHC.Event.Poll
----------------------------------+----------------------------------------
       Reporter:  ydewit          |             Owner:
           Type:  bug             |            Status:  new
       Priority:  normal          |         Milestone:
      Component:  libraries/base  |           Version:  7.8.2
       Keywords:                  |  Operating System:  MacOS X
   Architecture:                  |   Type of failure:  Building GHC failed
  Unknown/Multiple                |         Test Case:
     Difficulty:  Unknown         |          Blocking:
     Blocked By:                  |
Related Tickets:                  |
----------------------------------+----------------------------------------
 See the following section from base's GHC.Event.Poll module:
 {{{
 module GHC.Event.Poll
     (
       new
     , available
     ) where
 #include "EventConfig.h"
 #if !defined(HAVE_POLL_H)
 import GHC.Base
 new :: IO E.Backend
 new = error "Poll back end not implemented for this platform"
 available :: Bool
 available = False
 {-# INLINE available #-}
 #else
 #include 
 
            #9275: Missing import statement in GHC.Event.Poll ----------------------------------------+---------------------------------- Reporter: ydewit | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.8.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC failed | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------+---------------------------------- Description changed by ydewit: Old description:
See the following section from base's GHC.Event.Poll module: {{{ module GHC.Event.Poll ( new , available ) where
#include "EventConfig.h"
#if !defined(HAVE_POLL_H) import GHC.Base
new :: IO E.Backend new = error "Poll back end not implemented for this platform"
available :: Bool available = False {-# INLINE available #-} #else #include
import Control.Concurrent.MVar (MVar, newMVar, swapMVar) import Control.Monad ((=<<), liftM, liftM2, unless) import Data.Bits (Bits, FiniteBits, (.|.), (.&.)) import Data.Maybe (Maybe(..)) import Data.Monoid (Monoid(..)) import Data.Word import Foreign.C.Types (CInt(..), CShort(..)) import Foreign.Ptr (Ptr) import Foreign.Storable (Storable(..)) import GHC.Base import GHC.Conc.Sync (withMVar) import GHC.Enum (maxBound) import GHC.Num (Num(..)) import GHC.Real (ceiling, fromIntegral) import GHC.Show (Show) import System.Posix.Types (Fd(..))
import qualified GHC.Event.Array as A import qualified GHC.Event.Internal as E }}}
Note how there is a missing {{{import qualified GHC.Event.Internal as E}}} when {{{HAVE_POLL_H}}} is not defined.
The same issue is present in master.
New description:
 See the following section from base's GHC.Event.Poll module:
 {{{
 module GHC.Event.Poll
     (
       new
     , available
     ) where
 #include "EventConfig.h"
 #if !defined(HAVE_POLL_H)
 import GHC.Base
 new :: IO E.Backend
 new = error "Poll back end not implemented for this platform"
 available :: Bool
 available = False
 {-# INLINE available #-}
 #else
 #include 
 
            #9275: Missing import statement in GHC.Event.Poll ----------------------------------------+---------------------------------- Reporter: ydewit | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: libraries/base | Version: 7.8.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC failed | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------+---------------------------------- Changes (by ydewit): * status: new => patch Comment: Here is the patch: {{{ diff --git a/GHC/Event/Poll.hsc b/GHC/Event/Poll.hsc index bb0b6e5..2ed25be 100644 --- a/GHC/Event/Poll.hsc +++ b/GHC/Event/Poll.hsc @@ -14,6 +14,7 @@ module GHC.Event.Poll #if !defined(HAVE_POLL_H) import GHC.Base +import qualified GHC.Event.Internal as E new :: IO E.Backend new = error "Poll back end not implemented for this platform" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9275#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9275: Missing import statement in GHC.Event.Poll ----------------------------------------+---------------------------------- Reporter: ydewit | Owner: rwbarton Type: bug | Status: patch Priority: normal | Milestone: Component: libraries/base | Version: 7.8.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC failed | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------+---------------------------------- Changes (by rwbarton): * owner: => rwbarton -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9275#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
 
            #9275: Missing import statement in GHC.Event.Poll
----------------------------------------+----------------------------------
        Reporter:  ydewit               |            Owner:  rwbarton
            Type:  bug                  |           Status:  patch
        Priority:  normal               |        Milestone:
       Component:  libraries/base       |          Version:  7.8.2
      Resolution:                       |         Keywords:
Operating System:  MacOS X              |     Architecture:
 Type of failure:  Building GHC failed  |  Unknown/Multiple
       Test Case:                       |       Difficulty:  Unknown
        Blocking:                       |       Blocked By:
                                        |  Related Tickets:
----------------------------------------+----------------------------------
Comment (by Reid Barton 
 
            #9275: Missing import statement in GHC.Event.Poll ----------------------------------------+---------------------------------- Reporter: ydewit | Owner: rwbarton Type: bug | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC failed | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------+---------------------------------- Changes (by rwbarton): * status: patch => closed * resolution: => fixed Comment: Thanks, applied. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9275#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
- 
                 GHC GHC