[jhc] dynamic library support?
Mark Wotton
mwotton at gmail.com
Mon Aug 10 01:55:17 EDT 2009
On 07/08/2009, at 1:18 PM, John Meacham wrote:
> On Fri, Aug 07, 2009 at 12:32:22PM +1000, Mark Wotton wrote:
>> Colour me shocked, if I just comment out the main function, the
>> exported
>> functions work fine.
>
> Cool! I was hoping it would be that easy but wasn't quite sure as I
> have never tested it.
>
> I guess the only thing to get jhc to officially support creating C
> librares would be to add an option that will omit main and call gcc
> with
> slightly different options to compile a library. If we want to get
> fancy
> we could have it spit out an appropriate .h file as well :)
>
> I would happily help if someone wanted to work on this. It fits
> right in
> with jhc's strengths.
Ok, so I could probably do with a hand on this :)
I've hacked Main.hs and FromHs.hs so that if there's no main, it
silently ignores it and omits it from the list. (Obviously
this is sub-optimal, but it'll do for now until I have some clue what
I'm doing.)
My code works fine if I do actually have a main, but when I try on
code without, I get a rather confusing error message:
==============================================================
15:51 ~/projects/Hubris/sample % cat Test.hs
{-# LANGUAGE ForeignFunctionInterface #-}
import Foreign.C.Types
import Maybe
fibonacci :: Int -> Int
fibonacci n = fibs !! n
where fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
fibonacci_hs :: CInt -> CInt
fibonacci_hs = fromIntegral . fibonacci . fromIntegral
foreign export ccall fibonacci_hs :: CInt -> CInt
15:51 ~/projects/Hubris/sample % ~/src/jhc/jhc -v Test.hs
reading /usr/local/etc/jhc-0.6/targets.ini
reading /usr/local/etc/jhc-0.6/targets.ini
jhc -v Test.hs
jhc 0.6.2 (-n byxkainijid-8
)
Finding Dependencies...
Loading libraries: ["base","haskell98"]
Library: base-1.0 </usr/local/share/jhc-0.6/base-1.0.hl>
Library: haskell98-1.0 </usr/local/share/jhc-0.6/haskell98-1.0.hl>
Main [Test.hs] <Test.ho>
Fresh: <Test.ho>
Typechecking...
Compiling...
Collected Compilation...
PassStats
Could not find main function: Main.main
[FE at .CCall.fibonacci_hs::EPi (_::ELit (bits<int>::ESort #)) (ELit
(bits<int>::ESort #))]
-- typeAnalyzeMethods
Type analyzed methods
Jhc.List.!! \({Jhc.Prim.Int})
W at .fJhc.List.!! \({Jhc.Prim.Int})
-- typeAnalyze-Main-AfterMethod
-- Simplify-Main-One
-- Simplify-Main-One
-- Simplify-Main-One
Total: Main-One
└─E
└─Simplify
├─f-beta-reduce: 2
└─inline.OnceInLam: 1
-- typeAnalyze-Main-AfterSimp
-- Simplify-Main-Two
Total: Main-Two
-- Simplify-SuperSimplify no rules
Total: SuperSimplify no rules
-- BoxifyProgram
-- Boxy WorkWrap
-- Simplify-SuperSimplify after Boxy WorkWrap
-- Simplify-SuperSimplify after Boxy WorkWrap
-- Simplify-SuperSimplify after Boxy WorkWrap
Total: SuperSimplify after Boxy WorkWrap
└─E
└─Simplify
├─case-of-bottom: 1
├─case-of-case: 1
├─f-beta-reduce: 2
├─inline
│ ├─Many: 1
│ └─OnceInLam: 1
├─known-case.Int#: 1
├─let-coalesce: 1
└─let-from-case: 2
-- LambdaLift
1 lambdas not lifted
E
├─case: 11
├─case-alt: 16
├─error: 2
├─lambda: 7
├─let-binding: 9
├─lit: 12
├─other: 10
├─prim: 5
└─var-use: 34
-- Simplify-PostLiftSimplify
Total: PostLiftSimplify
PassStats
├─BoxifyProgram: 1
├─Boxy WorkWrap: 1
├─EtaExpansion-Main-AfterOne: 1
├─LambdaLift
│ └─E
│ └─LambdaLift
│ ├─doBigLift.Case.2: 1
│ └─doLiftR.Lambda.2: 1
├─PruneUnreachable: 3
├─Simplify-Main-One
│ └─E
│ └─Simplify
│ ├─f-beta-reduce
│ │ ├─Jhc.List.241_xs: 1
│ │ └─X at .fJhc.List.242_n@1: 1
│ └─inline.OnceInLam.W at .fJhc.List.!!: 1
├─Simplify-Main-Two: 1
├─Simplify-PostLiftSimplify: 1
├─Simplify-SuperSimplify after Boxy WorkWrap
│ └─E
│ └─Simplify
│ ├─case-of-bottom: 1
│ ├─case-of-case: 1
│ ├─f-beta-reduce
│ │ ├─x12983587: 1
│ │ └─x99400243: 1
│ ├─inline
│ │ ├─Many.(epheremal): 1
│ │ └─OnceInLam.Jhc.List.!!: 1
│ ├─known-case.Int#: 1
│ ├─let-coalesce: 1
│ └─let-from-case: 2
├─Simplify-SuperSimplify no rules: 1
├─typeAnalyze-Main-AfterMethod
│ └─Specialize
│ ├─body
│ │ ├─Jhc.List.!!.x60780920.Int: 1
│ │ └─W at .fJhc.List.!!.Jhc.List.v450.Int: 1
│ └─use
│ ├─Jhc.List.!!: 1
│ └─W at .fJhc.List.!!: 1
├─typeAnalyze-Main-AfterSimp: 1
└─typeAnalyzeMethods: 1
Converting to Grin...
Found 0 CAFs to convert to constants, 0 of which are recursive.
Recursive
Constant
CAFS
EP FOR FE at .CCall.fibonacci_hs::EPi (_::ELit (bits<int>::ESort #))
(ELit (bits<int>::ESort #))
Grin
-- Simplify-Grin
Simplify-Grin
├─Grin
│ └─Simplify
│ ├─Assign.unit-unit: 1
│ └─Subst.var: 4
└─Simplify
├─Omit.Bind: 5
└─ZeroVar.w164179474: 1
-- Simplify-Grin
progComb: can't find '"x_"'
======================================================
(the EP FOR FE@ stuff is just some tracing garbage that I've chucked
in to make sure I was getting something vaguely approximating sense.)
So where should I start looking? Is it worth sending a darcs patch for
what I have so far?
Cheers
Mark
More information about the jhc
mailing list