[GHC] #9275: Missing import statement in GHC.Event.Poll

GHC ghc-devs at haskell.org
Sun Jul 6 18:43:44 UTC 2014


#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 <poll.h>

 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.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9275>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list