#1426: warning about `import Control.Monad.Fix` being unused when mdo is used
---------------------------+------------------------------------------------
  Reporter:  Isaac Dupree  |          Owner:         
      Type:  bug           |         Status:  new    
  Priority:  normal        |      Milestone:         
 Component:  Compiler      |        Version:  6.6.1  
  Severity:  normal        |       Keywords:         
Difficulty:  Unknown       |             Os:  Unknown
  Testcase:                |   Architecture:  Unknown
---------------------------+------------------------------------------------
and the use is exported.  This should not be warned about since
 Control.Monad.Fix is supposed to be imported in modules that use mdo, to
 be portable or something. "You should import Control.Monad.Fix. (Note:
 Strictly speaking, this import is required only when you need to refer to
 the name MonadFix in your program, but the import is always safe, and the
 programmers are encouraged to always import this module when using the
 mdo-notation.)"

 {{{
 {-# OPTIONS_GHC -fglasgow-exts -fwarn-unused-imports #-}

 module Test where

 import Control.Monad.Fix

 isEven :: Int -> Maybe Int
 isEven n = if even n then Just n else Nothing

 puzzle :: [Int]
 puzzle = mdo (x, z) <- [(y, 1), (y^2, 2), (y^3, 3)]
              Just y <- map isEven [z+1 .. 2*z]
              return (x + y)
 }}}

 produces

 {{{
 Test.hs:5:0:
     Warning: Module `Control.Monad.Fix' is imported, but nothing from it
 is used,
                except perhaps instances visible in `Control.Monad.Fix'
              To suppress this warning, use: import Control.Monad.Fix()
 }}}

 Just doing `import Control.Monad.Fix()` wouldn't fulfill the purpose of
 importing that module!

 I wonder if there are any other special syntaxes (arrows maybe?) with this
 effect.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1426>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to