Bizarre Haskell Problem

2003-01-29 Thread Matthew Donadio
Hello,

I am having a bizarre Haskell problem that I am having difficulty
debugging.  I am not positive this is a compiler problem, but my results
are not making any sense.

I have attached a few source files which compiled with ghc-5.04.2
running under Win95.  The files were compiled as:

ghc -c DFT.lhs
ghc -c FFT1.lhs
ghc -c FFT2.lhs
ghc -c Main1.hs
ghc -c Mail2.hs
ghc -o test1 Main1.o FFT1.o DFT.o
ghc -o test2 Main2.o FFT2.o DFT.o

Running test1 gives the following results (the last line is wrong):

foo 19:[1,2,4,8,16,13,7,14,9,18,17,15,11,3,6,12,5,10]
rader1 19: [1,2,4,8,16,13,7,14,9,18,17,15,11,3,6,12,5,10]
foo 23:[1,5,2,10,4,20,8,17,16,11,9,22,18,21,13,19,3,15,6,7,12,14]
rader1 23: [1,5,2,10,4,20,8,17,16,11,9,22,18,21,1,4,8,18,22,6,19,2]

Running test2 gives the following results (these are the results I
expect):

foo 19:[1,2,4,8,16,13,7,14,9,18,17,15,11,3,6,12,5,10]
rader1 19: [1,2,4,8,16,13,7,14,9,18,17,15,11,3,6,12,5,10]
foo 23:[1,5,2,10,4,20,8,17,16,11,9,22,18,21,13,19,3,15,6,7,12,14]
rader1 23: [1,5,2,10,4,20,8,17,16,11,9,22,18,21,13,19,3,15,6,7,12,14]

The only difference bewteen the sources is that in FFT1.lhs, lines 215
and 217 are present, while in FFT2.lhs, they are commented out.  Note
that these two lines reference the parameter, f.  Also note that rader1
calls foo, so I am confused as to how that can produce different
results, as test1 shows.  FFT1.rader1 works for all n = 19, but fails
for n = 23 (n has to be prime, however).  Also, if I copy the offending
code from FFT1.lhs to a separate file, then I get the results I expect,
but this is a less than ideal solution.

ghc-5.04.2 was installed with the Windows Installer from the website.

If you play with the code, foo n should produce a permutation of the
sequence [1..(n-1)] for all prime n (ie, foo n produces the permutation
for a generator of the Galois field n).

I appologize in advance if this is a bug on my part, but based on what I
am seeing, I am getting results that should not happen.

Thanks.

-- 
Matthew Donadio ([EMAIL PROTECTED])



FFT2.lhs
Description: haskellprogram


Main2.hs
Description: haskellprogram


DFT.lhs
Description: haskellprogram


FFT1.lhs
Description: haskellprogram


Main1.hs
Description: haskellprogram


RE: bug with -O -ffi and multiple module

2003-01-29 Thread Simon Marlow
 Okay, here's a weird one.  There's something wrong with the 
 ffi when using
 -O and the foreign imports are from another module.  For example, our
 foreign module, foo.c contains functions:
 
void* openFile(char*fn);
void closeFile(void*f);
float readFloat(void*f);
 
 which are interfaced from foo.h.  We have a FooIntr.hs interface file,
 which looks like:
 
foreign import ccall foo.h openFile  c__openFile  :: Ptr 
 CChar - IO
(Ptr ())
foreign import ccall foo.h closeFile c__closeFile :: Ptr 
 () - IO ()
foreign import ccall foo.h readFloat c__readFloat :: Ptr () - IO
CFloat

I think what you're seeing here is an instance of this bug:

http://sourceforge.net/tracker/index.php?func=detailaid=655400group_id
=8032atid=108032

Workaround: use -#include instead of including the header file in the
FFI spec.

Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Bizarre Haskell Problem

2003-01-29 Thread Simon Marlow

 I am having a bizarre Haskell problem that I am having difficulty
 debugging.  I am not positive this is a compiler problem, but 
 my results
 are not making any sense.
 
 I have attached a few source files which compiled with ghc-5.04.2
 running under Win95.  The files were compiled as:
 
 ghc -c DFT.lhs
 ghc -c FFT1.lhs
 ghc -c FFT2.lhs
 ghc -c Main1.hs
 ghc -c Mail2.hs
 ghc -o test1 Main1.o FFT1.o DFT.o
 ghc -o test2 Main2.o FFT2.o DFT.o
 
 Running test1 gives the following results (the last line is wrong):
 
 foo 19:[1,2,4,8,16,13,7,14,9,18,17,15,11,3,6,12,5,10]
 rader1 19: [1,2,4,8,16,13,7,14,9,18,17,15,11,3,6,12,5,10]
 foo 23:[1,5,2,10,4,20,8,17,16,11,9,22,18,21,13,19,3,15,6,7,12,14]
 rader1 23: [1,5,2,10,4,20,8,17,16,11,9,22,18,21,1,4,8,18,22,6,19,2]
 
 Running test2 gives the following results (these are the results I
 expect):
 
 foo 19:[1,2,4,8,16,13,7,14,9,18,17,15,11,3,6,12,5,10]
 rader1 19: [1,2,4,8,16,13,7,14,9,18,17,15,11,3,6,12,5,10]
 foo 23:[1,5,2,10,4,20,8,17,16,11,9,22,18,21,13,19,3,15,6,7,12,14]
 rader1 23: [1,5,2,10,4,20,8,17,16,11,9,22,18,21,13,19,3,15,6,7,12,14]

Your problem is that rader1 has different types in FFT1 and FFT2:

   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.04.2, for Haskell
98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
:Prelude :l FFT1
Skipping  DFT  ( DFT.lhs, DFT.o )
Skipping  FFT1 ( FFT1.lhs, ./FFT1.o )
Ok, modules loaded: FFT1, DFT.
Prelude FFT1 :t rader1
forall a b.
(Integral a,
 GHC.Arr.Ix a,
 Num (Data.Complex.Complex b),
 RealFloat b) =
GHC.Arr.Array a (Data.Complex.Complex b) - a - [a]
Prelude FFT1 :t rader1 (gendata 23) 23
[Int]
Prelude FFT1 :l FFT2
Skipping  DFT  ( DFT.lhs, DFT.o )
Skipping  FFT2 ( FFT2.lhs, ./FFT2.o )
Ok, modules loaded: FFT2, DFT.
Prelude FFT2 :t rader1
forall a t. (Integral a, GHC.Arr.Ix a) = t - a - [a]
Prelude FFT2 :t rader1 (gendata 23) 23 
forall a. (Integral a, GHC.Arr.Ix a) = [a]

So in FFT2, defaulting will force the type variable a to Integer,
whereas in FFT1 the type has already been forced to Int.  I imagine that
with Int you're getting some overflow, leading to the incorrect results.

Moral of this story: type signatures can help to avoid unexpected
behaviour...

Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Core, shadowing type variable names, possible fix

2003-01-29 Thread Tobias Gedell
I have found what causes the bug and implemented a possibly fix for it. 
The problem has to do with source types that aren't expanded before 
tidying them.

Here is a small example where the error occurs:

-
module Test where

newtype A a = A (forall b. b - a)

test :: forall q b. q - A b
test _ = undefined
-


When generating Core for this program we get:

-
%module Test
  %newtype Test.A a = %forall b . b - a;
  Test.A :: %forall a . (%forall b . b - a) - %forall b . b - a =
%note InlineMe
\ @ a (tpl::%forall b . b - a) - tpl;
  Test.zdgfromA :: %forall a . (%forall b . b - a) -
			   %forall b . b - a =
\ @ a (g::%forall b . b - a) - g;
  Test.zdgtoA :: %forall a . (%forall b . b - a) -
			 %forall b . b - a =
Test.A;
  Test.test :: %forall q b . q - %forall b . b - b =
\ @ q @ b (ds::q) - GHCziErr.undefined @ (%forall b . b - b);
-

Here the type for Test.test is wrong since the second binding of b 
shadows the first binding of b. We do also pass the wrong type to 
GHCziErr.undefined.

The tidyXXX functions should take care of this and rename the second b 
to b1. After diving into GHC I found that the problem is that the types 
and expressions are tidied before the source types are expanded. When 
generating external core the source types are expanded first in make_ty 
in MkExternalCore.lhs.


I believe that there are three possible fixes:

 1. Make sure that all type variables that are bound in non recursive 
newtypes are made unique
 2. Expand all non recursive newtypes before using tidyXXX
 3. Not expand the non recursive newtypes when generating external core


I have implemented the third alternative. I changed the function make_ty 
in MkExternalCore.lhs to:

-
make_ty :: Type - C.Ty
make_ty (TyVarTy tv) = C.Tvar (make_var_id (tyVarName tv))
make_ty (AppTy t1 t2) = C.Tapp (make_ty t1) (make_ty t2)
make_ty (TyConApp tc ts) = foldl C.Tapp (C.Tcon (make_con_qid (tyConName 
tc))) (map make_ty ts)
make_ty (FunTy t1 t2) = make_ty (TyConApp funTyCon [t1,t2])
make_ty (ForAllTy tv t) = C.Tforall (make_tbind tv) (make_ty t)
make_ty (SourceTy (NType tc ts)) = foldl C.Tapp (C.Tcon (make_con_qid 
(tyConName tc))) (map make_ty ts)
make_ty (SourceTy p) = make_ty (sourceTypeRep p)
make_ty (NoteTy _ t) = make_ty t
-


Now the generated Core for the program listed above becomes:

-
%module Test
  %newtype Test.A a = %forall b . b - a;
  Test.A :: %forall a . (%forall b . b - a) - Test.A a =
%note InlineMe
\ @ a (tpl::%forall b . b - a) - tpl;
  Test.zdgfromA :: %forall a . Test.A a - %forall b . b - a =
\ @ a (g::Test.A a) - g;
  Test.zdgtoA :: %forall a . (%forall b . b - a) - Test.A a =
Test.A;
  Test.test :: %forall q b . q - Test.A b =
\ @ q @ b (ds::q) - GHCziErr.undefined @ (Test.A b);
-




Sincerely,
 Tobias

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs