[GHC] #12596: can't find interface-file declaration
GHC
ghc-devs at haskell.org
Thu Sep 15 16:26:21 UTC 2016
#12596: can't find interface-file declaration
-------------------------------------+-------------------------------------
Reporter: mwotton | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
@@ -3,1 +3,1 @@
- ```
+ {{{
@@ -12,1 +12,3 @@
- ```
+ }}}
+
+ The code is
New description:
full repro at https://github.com/mwotton/liftwoes/issues/1
{{{
/home/mark/projects/liftwoes/src/Lib.hs:14:11: error:
• Can't find interface-file declaration for variable
Data.Text.Internal.pack
Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the error
• In the first argument of ‘(:)’, namely
‘Data.Text.Internal.pack ((:) 'A' [])’
In the first argument of ‘HS.fromList’, namely
}}}
The code is
{{{#!hs
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Lib where
import Data.Data
import qualified Data.Set as HS
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Time
-- import Instances.TH.Lift
import Instances
import Language.Haskell.TH.Syntax
table = $(do r <- runIO (HS.fromList . T.lines <$> T.readFile
"/usr/share/dict/words")
[|r|] )
someFunc = do
print $ HS.member "foo" table
}}}
--
Comment (by simonpj):
Yes, `bytemyapp` on the [https://github.com/mwotton/liftwoes/issues/1
github repo] is right. Here's a shorter example
{{{
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module T12596 where
import qualified Data.Set as HS
import qualified Data.Text as T
import Language.Haskell.TH.Syntax
table = $(do let r2 :: T.Text
r2 = "he" :: T.Text
liftData r2 )
}}}
* `liftData` is defined in `Language.Haskell.TH.Syntax`:
{{{
liftData :: Data a => a -> Q Exp
liftData = dataToExpQ (const Nothing)
}}}
* So we need `Data Text`. The `Data` class is intended to describe
algebraic data types, but the `text` package cleverly uses it to make
`Text` behave like an algebraic data type, even though it isnt'.
* Using the `toConstr` method of `instance Data Text` (in module
`Data.Text`), it pretends that `Text` has a data constructor called `pack
:: String -> Text`. This function is defined in `Data.Text`.
* But `toConstr :: Data a => a -> Constr` and `Constr` is a record giving
only the ''string name'' of the constructor.
{{{
data Constr = Constr { conrep :: ConstrRep
, constring :: String
, confields :: [String] -- for AlgRep only
, confixity :: Fixity -- for AlgRep only
, datatype :: DataType }
}}}
It was really only intended for 'show'.
* But here it's being used `Language.Haskell.TH.Syntax.dataToQa` to make a
Template Haskell `Name` for `pack`. It uses `mkNameG_v` passing the
string for the "data constructor" (`pack`) but the module for the type
constructor. That is, `dataToQa` assumes that the data constructor is
defined in the same module as the type constructor, which is usually
reasonable. Moreover, it has no other choice because `Constr` simply
doesn't record the full, original `Name` of the data constructor.
So that's the story. It took me some while to puzzle it out! And it's
clearly unhelpful to users.
Meanwhile, what can we do?
* Refactor the `text` package so that the function mentioned in
`Data.Text.packConstr` is actually defined in the same module as the data
type `Text` itself.
* (Better.) Make `Data.Data.Constr` contain a Template Haskell `Name` for
the data constructor, rather than just a `String`. Doing that would mean
moving `Language.Haskell.TH.Syntax.Name` (and associated types and
functions) to package `base`. This would make sense to me; class `Data`
is really about meta-programming. The `constring` record selector could
be come an ordinary function, so almost all programs would work fine.
Any opinions.?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12596#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list