[Haskell-cafe] ANNOUNCE: jhc 0.7.1

Eugene Kirpichov ekirpichov at gmail.com
Tue Aug 25 03:24:01 EDT 2009


WOW! Congratulations, I am impressed: I ran it on a small example
program and jhc produced output that was 3x faster than ghc -O2!
Serious stuff.

However: I tried it on a different very simple program (a projecteuler one):

module Main where
isReversible n | n`mod`10 == 0 = False
               | otherwise = all (`elem` "1357") . show $ (n +
(read.reverse.show$n))
main = putStrLn . show . length . filter isReversible $ [1..1000000::Int]

ghc took 6s on this one, whereas jhc took 2 minutes real time (of
which 5s user time and 5s system time), which also froze the system
completely! Most probably it allocated a ton of memory, because the
system was very slow for a while after the program completed.

Same thing happened with a different but bigger number-crunching program.

Also: I tried to build a program that uses uvector, and for that I
needed an uvector.hl file: I unarchived the package and did this:
jkff at jkff-laptop:~/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4$
jhc --build-hl uvector.cabal
jhc --build-hl uvector.cabal
jhc 0.7.1 (0.7.0-13)
Creating library from description file: "uvector.cabal"
Reading: "uvector.cabal"
Finding Dependencies...
Using Ho Cache: '/home/jkff/.jhc/cache'
Typechecking...
Compiling...
Writing Library: uvector-0.1.0.4.hl
jkff at jkff-laptop:~/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4$
ls -l uvector-0.1.0.4.hl
-rw-r--r-- 1 jkff jkff 1248 2009-08-25 10:58 uvector-0.1.0.4.hl

(is it correct that actually no compilation occured at all?)

jkff at jkff-laptop:~/projects/for-fun/haskell/mandelbrot$ jhc -p
/home/jkff/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4/uvector-0.1.0.4.hl
Low.hs
jhc -p /home/jkff/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4/uvector-0.1.0.4.hl
Low.hs
jhc 0.7.1 (0.7.0-13)
Finding Dependencies...
Using Ho Cache: '/home/jkff/.jhc/cache'
Library was not found
'/home/jkff/.cabal/packages/hackage.haskell.org/uvector/0.1.0.4/uvector-0.1.0.4/uvector-0.1.0.4.hl'

Now this seems strange.

The documentation to jhc was not of much help. What should be done to
use libraries from hackage?
Would it be hard to give jhc some integration with ghc's package.conf?

2009/8/25 John Meacham <john at repetae.net>:
> Hi, I am happy to announce the jhc optimizing haskell compiler version 0.7.1.
>
> Information on installing jhc is here: http://repetae.net/computer/jhc/building.shtml
> And the Main page is here:  http://repetae.net/computer/jhc
>
> There have been a lot of changes since the last public release, Some
> notable ones are:
>
>  * The use of a general compiler cache by default rather than object
>   files. This means work done by jhc is shared between projects, jhc
>   uses cryptographic hashes internally to never compile the same piece of
>   code more than once. This has numerous benefits, a notable one being
>   speed.
>  * Reworked library support. Jhc libraries are now much more general,
>   when linking only the bits needed are loaded from the hl
>   file, libraries are allowed to re-export modules from other
>   libraries, making versioning or providing multiple interfaces to the
>   same functionality a lot simpler. Library conflicts are 'lazy', like
>   ambiguity errors now.
>  * Updated Manual, clearer build instructions
>  * Support for writing pure C libraries in Haskell.
>  * numerous library updates, filled out many IO routines that were stubs
>   before
>  * Smart progress meters when compiler for a better user experience
>  * performs all typechecking before compilation, for a faster
>   edit-compile loop when writing code with jhc.
>  * various bug fixes
>  * Cross Compilation improvements, for instance you can compile for windows transparently on
>   a linux box. Or for an embedded target that is independent of the
>   host.
>  * Better Mac OSX Support, as both a host and target.
>
>
> If you are wondering about the large version number bump since the last
> release, It is because several versions were released only internally to
> the jhc list for testing. If you are interested in jhc, join the list at:
> http://www.haskell.org/mailman/listinfo/jhc
>
>        John
>
> --
> John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru


More information about the Haskell-Cafe mailing list