The attached program fails to compile despite it being a close
copy of that shown in the Reference: comments.  The ghci invocation
results in:

================================
~/prog_dev/haskell/my-code $ ghci Modules.hs
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Test             ( Modules.hs, interpreted )


Modules.hs:12:0: parse error on input `module'
Failed, modules loaded: none.
Prelude> :q
Leaving GHCi.

==================================
What should change to allow compilation?

TIA.

-Larry


{-
  Purpose:
    Show that multiple modules can occur in same file.
  Reference:
    First code example here:
      http://www.haskell.org/onlinereport/haskell2010/haskellch5.html#x11-980005
-}

module Main where
  main :: IO ()
  
  main = 
    do
      putStrLn "Begin IoDemo.hs:"
      val1 <- return 123
      val2 <- return 345
      print (val1+val2+Test.test)

module Test where
  test = 5

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to