[GHC] #13254: Confusing error message from GHCI - "defined in multiple files" shows the same file
GHC
ghc-devs at haskell.org
Thu Feb 9 13:25:11 UTC 2017
#13254: Confusing error message from GHCI - "defined in multiple files" shows the
same file
-------------------------------------+-------------------------------------
Reporter: ocharles | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 8.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I just had the following very confusing exchange with GHCI:
{{{
λ :load
Ok, modules loaded: none.
λ :load src/Application/Aws.hs
Ok, modules loaded: Application.Aws (dist/build/Application/Aws.o).
λ private
<interactive>:3:1: error: Variable not in scope: private
λ :m *Application.Aws
module 'Application.Aws' is not interpreted; try ':add *Application.Aws'
first
λ :add *Application.Aws
<no location info>: error:
module ‘circuithub-api-0.0.4-EeGo4QUTODrB58BZrr3htj:Application.Aws’
is defined in multiple files: src/Application/Aws.hs
src/Application/Aws.hs
Failed, modules loaded: Application.Aws (dist/build/Application/Aws.o).
λ :! ghc --version
The Glorious Glasgow Haskell Compilation System, version 8.1.20161115
}}}
This can really be simplified to
{{{
λ :load src/Application/Aws.hs
Ok, modules loaded: Application.Aws (dist/build/Application/Aws.o).
λ :add *Application.Aws
<no location info>: error:
module ‘circuithub-api-0.0.4-EeGo4QUTODrB58BZrr3htj:Application.Aws’
is defined in multiple files: src/Application/Aws.hs
src/Application/Aws.hs
Failed, modules loaded: Application.Aws (dist/build/Application/Aws.o).
}}}
For the record, here is Application.Aws:
{{{#!hs
{-# LANGUAGE DeriveDataTypeable #-}
module Application.Aws
( AwsExtra(..)
) where
import Prelude
import Data.Data (Data)
import Data.ByteString.Char8
import Data.Text
data AwsExtra = AwsExtra
{ awsKey :: ByteString
, awsSecret :: ByteString
, awsS3AssetsBucket :: Text
} deriving (Show,Data)
private :: Int
private = 42
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13254>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list