green-card in fptools-4.08

2000-07-16 Thread trb

Hi,

I've built fptools-4.08 from the cvs sources on my x86 linux box. But green-card
would not build. I fiddled with its src/Makefile as below:

# SRC_HC_OPTS+= -fvia-C -fglasgow-exts -syslib text -syslib data -syslib util 
-recomp -Rghc-timing -O
SRC_HC_OPTS+= -fvia-C -fglasgow-exts -package text -package data -package util 
-recomp -Rghc-timing -O

which helped. But finally the build failed with:

/usr/local/ghc/bin/ghc -fvia-C -fglasgow-exts -package text -package data -package 
util -recomp -Rghc-timing -O  -cpp -DBEGIN_GHC_ONLY='-}' -DEND_GHC_ONLY='{-' 
-DBEGIN_NOT_FOR_GHC='{-' -DEND_NOT_FOR_GHC='-}'  -c GreenCard.lhs -o GreenCard.o -osuf 
o
<>
/usr/local/ghc/bin/ghc -c ErrorHook.c -o ErrorHook.o
windres ExeVersionInfo.rc ExeVersionInfo.o
make[1]: windres: Command not found
make[1]: *** [ExeVersionInfo.o] Error 127
make: *** [all] Error 1

Why is it trying to compile Windoze resources on a Linux box ?? How can I stop
it ?

Any suggestions would be appreciated.

Tim




No Subject

2000-07-16 Thread Robert Will



 $ ghc -O -O2-for-C -fvia-c -o teiler teiler.hs
panic! (the `impossible' happened):
funResultTy t{-r270-}
Please report it as a compiler bug to [EMAIL PROTECTED]

 $ gcc -dumpversion
2.95.2
 $ ghc --version
The Glorious Glasgow Haskell Compilation System, version 4.05, patchlevel
0

it works without -O, doesn't with -O2

cu, Robert
-- 
Join the best: news://tui.programming_contest
http://www.tu-ilmenau.de/~robertw/icpc


main = einzeln $ numslist $ genlist []

einzeln (x:xs) = do
  print x
  getLine
  einzeln xs

sonst = True

primes  :: Integral a => [a]
primes   = map head (iterate sieve [2..])
sieve (p:xs) = [ x | x<-xs, x `rem` p /= 0 ]

type Forest a = [Tree a]
data Tree a   = Tree a (Forest a) deriving (Show, Eq, Ord)

generate ps = Tree (zahl ps, teiler ps) (map generate pss)
  where pss = filter sorted $ zipWith inc_ith [1..length ps +1] (repeat ps)
inc_ith 1 [] = [1]
inc_ith 1 (x:xs) = x+1 : xs
inc_ith n (x:xs) = x : inc_ith (n-1) xs
-- Liste kann höchstens um 1 kürzer sein, als n

sorted [] = True
sorted [x] = True
sorted (x:y:xs) = (x>=y) && (sorted (y:xs))

zahl ps = product $ zipWith (^) primes ps
teiler ps = product $ map (+1) ps

nums (Tree x@(_,n) ts) = x : (nums $ purge (\(_,xn) -> xn<=n) $ reTree ts)

purge :: Ord a => (a->Bool) -> Tree a -> Tree a
{- Knoten, die p erfüllen, werden unter Nachrutschen entfernt -}
purge p (Tree x ts) | p x = reTree rs
| sonst = Tree x rs
where rs = map (purge p) ts

reTree :: Ord a => Forest a -> Tree a
{- kleinste Wurzel der Teilbäume wird die gemeinsame Wurzel -}
reTree ts = Tree min $ map (plop min) ts
where min = minimum $ map (\(Tree x _) -> x) ts
  plop m t@(Tree x ts) | m==x  = reTree ts
   | sonst = t

-- try: nums $ generate []

genlist ps = (zahl ps, teiler ps) : foldl merge [] (map genlist pss)
  where pss = filter sorted $ zipWith inc_ith [1..length ps +1] (repeat ps)
inc_ith 1 [] = [1]
inc_ith 1 (x:xs) = x+1 : xs
inc_ith n (x:xs) = x : inc_ith (n-1) xs
-- Liste kann höchstens um 1 kürzer sein, als n

merge [] ys = ys
merge xs [] = xs
merge (x:xs) (y:ys) | x==y  = x : merge xs ys
| x xn>n ) xs)


-- Versuchsfunktionen

-- Wie oft ist p als Faktor in x enthalten?
drin x p | mod x p == 0 = 1+ drin (div x p) p
 | sonst = 0

purgeh h (Tree x []) = Tree x []
purgeh 0 (Tree x _)  = Tree 0 []
purgeh h (Tree x ts) = Tree x $ map (purgeh (h-1)) ts

gen :: Int -> Tree Int
gen 0 = Tree 1 []
gen n = Tree (n+1) $ map gen [0..div n 2]

suml (Tree x []) = x
suml (Tree x ts) = sum $ map suml ts

verteile n k = suml $ purgeh k $ gen n





Re:

2000-07-16 Thread Sven Panne

Robert Will wrote:
> [...] it works without -O, doesn't with -O2

Neither ghc-4.08 nor the CVS version have this problem, so you
should probably upgrade, these versions are much more stable than
4.05 anyway. And -fvia-c should probably be -fvia-C. GHC doesn't
always report unknown options (we should definitely fix that).

Cheers,
   Sven




Re: What is `AClass'?

2000-07-16 Thread Michael Weber

On Sun, Jul 16, 2000 at 16:49:35 -0700, Martin Pokorny wrote:
> Hi all,
> 
> I'm a beginner to functional programming and Haskell, so please bear
> with me. I am working on some numerical programming routines, and I
> ran into a small problem trying to compile a module of mine. I'm using
> ghc version 4.08.0, which I downloaded from Michael Weber's web site
> for my Debian Gnu/Linux system. The compilation stops before producing
> an object file and prints out `AClass', with no further output. Is
> there something else I can do to get more information regarding this
> failure (besides the -v option, which I tried to no avail)? Or should
> I just try to isolate this problem and post the code to this list for
> further help?

[Cc & F'up to [EMAIL PROTECTED] set]

Hi!

can you please send the source which produced the fault? If possible,
try to narrow it as much as you can...

Marcin reported a fault with AClass before, it looked like this:

module Test where

class Lookup c k a where
lookupAll :: Sequence seq a => c -> k -> seq a

class Lookup (s a) Int a => Sequence s a where
foo :: s a


panic! (the `impossible' happened):
AClass .Test.Sequence{-r8,x-}



Did the compiler output look similar? Or was it really just `AClass'?


Cheers,
Michael
-- 
 /~\ ASCII ribbon | "i have decided to release the first 24GB of my genetic
 \ / campaign |  code under the Artistic License. since this is DFSG
  X  against  |  compatible, could it go in main?"
 / \ HTML mail|  -- debian-devel <[EMAIL PROTECTED]>