6.4.1 for SuSE-10.0 lib64

Serge D. Mechveliani mechvel at botik.ru
Fri Mar 17 08:57:14 EST 2006


Dear GHC team,

We are trying to install  ghc-6.4.1 
on
  SuSE Linux 10.0,  lib64.

First, we install it to the system area  from binary  found on the GHC www 
page as
          Binary x86,  Generic Linux with glib 2.3.
Now, 
    ~> rpm -qa | grep compat
says 
  compat-curl2-32bit-7.11.0-7.2
  compat-32bit-2004.11.13-4
  compat-libstdc++-5.0.7-6
  compat-readline4-4.3-4
  compat-2004.11.13-4
  compat-curl2-7.11.0-7.2

Then,  ghc  makes the project (under Cabal), creates  .o, .a  libraries,
after
       runhaskell Setup.hs install --user

Then,   ghc $dmCpOpt --make Main

'makes' the user module and needs to link all libraries. It reports
---------
Chasing modules from: Main
Skipping  Main             ( Main.hs, Main.o )
Linking ...
/usr/lib64/gcc/x86_64-suse-linux/4.0.2/../../../../x86_64-suse-linux/bin/ld: cannot find -lreadline
collect2: ld returned 1 exit status
source/demotest>   
---------

We simplified the project to a single module

 module DPrelude (sublists)
 where
 sublists :: [a] -> [[a]]
 sublists []     =  [[]]
 sublists (x:xs) =  (map (x:) ls) ++ ls  where  ls = sublists xs

The libraries are made of this module. The "user" program is

 module Main 
 where
 import DPrelude
 main =
   let ll = sublists [1, 2 :: Integer]
   in
   putStr "abc" >> writeFile "fl" "abc" >> getChar
   >>
   putStr (shows ll "\n")
   >>
   appendFile "fl" "1"

And it faills with this"readline".

-------------------------------------------------------------------------
Then, we try the module which does not use newly created library,
but uses input-output:

 main = putStr "abc" >> writeFile "fl" "abc" >> getChar
        >>
        putStr "abc"  >>  appendFile "fl" "1"

And it makes and runs all right.

------------------------------------------------------------------------
Then, I tried to "make" GHC from source by this binary GHC.
"configure" does not tell anything about Alex and Happy -- although
I do not see them (forgotten of them). 
It finishes with                   exit 0,
as if nothing has happened.
Then,  
      > make

reports something which ends (after a couple of minutes) with

utils/PrimPacked.lhs:263:0:
    Warning: foreign declaration uses deprecated non-standard syntax
In file included from /tmp/ghc31185.hc:6:
/usr/local/lib/ghc-6.4.1/include/HsReadline.h:5:31: error: readline/readline.h:\
 No such file or directory
/usr/local/lib/ghc-6.4.1/include/HsReadline.h:6:30: error: readline/history.h: \
No such file or directory
<<ghc: 101068136 bytes, 20 GCs, 3654882/7854280 avg/max bytes residency (4 samp\
les), 20M in use, 0.00 INIT (0.00 elapsed), 0.27 MUT (0.81 elapsed), 0.11 GC (0\
.13 elapsed) :ghc>>
make[2]: *** [stage1/utils/PrimPacked.o] Error 1
make[1]: *** [all] Error 1
make[1]: Leaving directory `/home/mechvel/ghc/6.4.1/ghc-6.4.1/ghc'
make: *** [build] Error 1


Please, can you advise, how to make   ghc-6.4.1  work under the above system?
Does it matter the difference between  lib64 and lib32 ?
(we could remain with lib32).


-----------------
Serge Mechveliani
mechvel at botik.ru







More information about the Glasgow-haskell-users mailing list