#2428: bad error message for multiple modules in the same file
-----------------------------+----------------------------------------------
    Reporter:  Isaac Dupree  |       Owner:          
        Type:  bug           |      Status:  new     
    Priority:  normal        |   Component:  Compiler
     Version:  6.8.2         |    Severity:  normal  
    Keywords:                |    Testcase:          
Architecture:  Unknown       |          Os:  Unknown 
-----------------------------+----------------------------------------------
 consider this file:
 {{{
 module MyMod where
 foo :: Int
 foo = 3

 module Main (main) where
 import MyMod (foo)
 main :: IO ()
 main = print foo
 }}}

 The layout rule dictates that this parses properly (the first module
 clause ends when the second "module" gives a parse error, just like "in"
 ends a "let"); this gets the same error:
 {{{
 module MyMod where
  { foo :: Int; foo = 3 }
 module Main (main) where
  { import MyMod (foo); main :: IO (); main = print foo }
 }}}

 The Haskell98 report doesn't say anything about how modules are expected
 to be laid out in files, so I had assumed it would work.  The error is
 {{{
 parse error on input `module'
 }}}
 (except if Main comes before `MyMod`, ''and'' --make is used with ghc, we
 get
 {{{
 Could not find module `MyMod':
 Use -v to see a list of the files searched for.
 }}}
 even though `MyMod` is clearly (to a human) in that very file.)

 It took me a long time to figure out what was wrong and what I had to do.
 Admittedly I'm only slightly interested in GHC implementing support to
 allow this, since if multiple files are involved at all it causes module-
 finding trouble (obviously to me now); mostly I just want a good error
 message, maybe something like "Each file must contain exactly one module.
 Any module intended to be imported must be in an appropriately named file,
 e.g. module `Module.Name' goes in `Module/Name.hs'."

 ( This happened to me a long time ago... but I was reminded by #2427 )

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

Reply via email to