Cannot find normal object file when compiling TH code

Yorick Laupa yo.eight at gmail.com
Thu Jan 2 22:44:28 UTC 2014


Except expected #7021 error message, it works on my machine (Archlinux
x86_64) with --dynamic-too


2014/1/2 Carter Schonwald <carter.schonwald at gmail.com>

> would --dynamic-too work too?
>
>
> On Thu, Jan 2, 2014 at 5:36 PM, Yorick Laupa <yo.eight at gmail.com> wrote:
>
>> Hi Carter,
>>
>> Someone figured it out on #ghc. It seems we need to compile with -dynamic
>> when having TH code now (https://ghc.haskell.org/trac/ghc/ticket/8180)
>>
>> About a snippet, I working on that ticket (
>> https://ghc.haskell.org/trac/ghc/ticket/7021) so it's based on the given
>> sample:
>>
>> -- Tuple.hs
>> {-# LANGUAGE ConstraintKinds, TemplateHaskell #-}
>>
>> module Tuple where
>>
>> import Language.Haskell.TH
>>
>> type IOable a = (Show a, Read a)
>>
>> foo :: IOable a => a
>> foo = undefined
>>
>> test :: Q Exp
>> test = do
>>     Just fooName <- lookupValueName "foo"
>>     info         <- reify fooName
>>     runIO $ print info
>>     [| \_ -> 0 |]
>> --
>>
>> -- Main.hs
>> {-# LANGUAGE TemplateHaskell #-}
>> module Main where
>>
>> import Tuple
>>
>> func :: a -> Int
>> func = $(test)
>>
>> main :: IO ()
>> main = print "hello"
>>
>> --
>>
>>
>> 2014/1/2 Carter Schonwald <carter.schonwald at gmail.com>
>>
>>> Did you build ghc with both static and dynamic libs? Starting in
>>> 7.7/HEAD, ghci uses Dylib versions of libraries, and thus TH does too.
>>>  What OS and architecture is this, and what commit is your ghc build from?
>>>
>>> Last but most importantly, if you don't share the code, we can't really
>>> help isolate the problem.
>>>
>>>
>>> On Thursday, January 2, 2014, Yorick Laupa wrote:
>>>
>>>> Hi,
>>>>
>>>> Oddly I can't compile code using TH with GHC HEAD. Here's what I get:
>>>>
>>>> cannot find normal object file './Tuple.dyn_o'
>>>>     while linking an interpreted expression
>>>>
>>>> I'm currently working on a issue so I compile the code with ghc-stage2
>>>> for convenience.
>>>>
>>>> I found an old ticket related to my problem (
>>>> https://ghc.haskell.org/trac/ghc/ticket/8443) but adding
>>>> -XTemplateHaskell didn't work out.
>>>>
>>>> The code compiles with ghc 7.6.3.
>>>>
>>>> Here's my setup: Archlinux (3.12.6-1)
>>>>
>>>> Any suggestions ?
>>>>
>>>> --Yorick
>>>>
>>>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/ghc-devs/attachments/20140102/9f244fc8/attachment.html>


More information about the ghc-devs mailing list