The boot interface files for TypeRep contain errors

2003-02-06 Thread Tobias Gedell
The boot interface files for .../ghc/compiler/types/TypeRep.lhs contain 
errors.


In TypeRep.lhs PredType is defined as:

-
type PredType  = SourceType	-- A subtype for predicates
-


But in the boot files it is exported as a datatype (taken from 
TypeRep.hi-boot-6):

-
module TypeRep where

data Type
data PredType
type Kind = Type
type SuperKind = Type
-

When compiling GHC this doesn't matter, the compilation succeeds anyway. 
The error shows up first when generating external Core for GHC. Since 
PredType is exported as a datatype it will be refered to by all modules 
that are using the boot file, but when generating external Core for 
TypeRep the type PredType will be removed since it is just an alias. 
Therefore there will be a lot of references to the nonexisting type 
TypeRep.PredType.


The solution is to define PredType as a type in the boot files and add 
the type SourceType as a datatype.


Here are the modified boot files:

TypeRep.hi-boot:
-
_interface_ TypeRep 1
_exports_ TypeRep Type SourceType PredType Kind SuperKind ;
_declarations_
1 data Type ;
1 data SourceType ;
1 type PredType = SourceType;
1 type Kind = Type ;
1 type SuperKind = Type ;
-


TypeRep.hi-boot-5
-
__interface TypeRep 1 0 where
__export TypeRep Type SourceType PredType Kind SuperKind ;
1 data Type ;
1 data SourceType ;
1 type PredType = SourceType ;
1 type Kind = Type ;
1 type SuperKind = Type ;
-


TypeRep.hi-boot-6
-
module TypeRep where

data Type
data SourceType
type PredType = SourceType
type Kind = Type
type SuperKind = Type
-



Should I commit these changes to the HEAD branch?



Regards,
 Tobias

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


Re: The boot interface files for TypeRep contain errors

2003-02-06 Thread Tobias Gedell
Urk!  Good point!

Yes, please do commit those changes. Do you have commit permission now?


Yes, I have commit permission now, thanks!

I had troubles commiting at first but then I ran cvs update -A and 
then cvs commit filenames. I hope that was the right way to do it.



//Tobias


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


Looking for large Haskell programs

2003-02-04 Thread Tobias Gedell
Hi,

I'm looking for large haskell programs with more than 15000 lines of 
code. Does any of you know where I can find such programs? The programs 
found in the nofib suite are not large enough.


//Tobias

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Looking for large Haskell programs

2003-02-04 Thread Tobias Gedell
 GHC is such a program, as are the other Haskell compilers.  Perhaps too
 complicated for your purposes, though.

GHC has too many mutually recursive modules to be useful, otherwise it
would be great! But I will look more into the other compilers, are they
written in Haskell?, thanks for the suggestion!


 I can give you a few ~5000-1 line programs if you want.  I don't 
quite
 have anything as large as 15000 lines, though.

I have quite many 5-10k programs, but thanks anyway!

I really need programs with more than 15000 lines of code.



//Tobias


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Core, Unit and Z0T

2003-01-30 Thread Tobias Gedell
Are Unit and Z0T considered equal?


In GHC/Base.hcr they are both defined:

-
  %data GHCziBase.Unit =
{GHCziBase.Unit};
  %data GHCziBase.Z0T =
{GHCziBase.Z0T};
-


In .../ghc/compiler/prelude/primops.txt at line 2669 we find:

-
primop  FinalizeWeakOp finalizeWeak# GenPrimOp
   Weak# a - State# RealWorld - (# State# RealWorld, Int#,
  (State# RealWorld - (# State# RealWorld, Unit #)) #)
   with
   usage= { mangle FinalizeWeakOp [mkM, mkP]
   (mkR . (inUB FinalizeWeakOp
[id,id,inFun FinalizeWeakOp 
mkR mkM])) }
   has_side_effects = True
   out_of_line  = True
-

Here Unit is used but in .../GHC/Weak.hcr at line 57 when using 
GHCziPrim.finalizzeWeakzh it is tried to unify with Z0T:

-
  GHCziWeak.finalizze :: %forall v . GHCziWeak.Weak v -
 GHCziIOBase.IO GHCziBase.Z0T =
\ @ v
  (ds::GHCziWeak.Weak v)
  (eta::GHCziPrim.Statezh GHCziPrim.RealWorld) -
	%case ds %of (wild::GHCziWeak.Weak v)
	  {GHCziWeak.Weak (w::GHCziPrim.Weakzh v) -
	 %case (GHCziPrim.finalizzeWeakzh @ v w eta)
	 %of (wild1::GHCziPrim.Z3H
			 (GHCziPrim.Statezh GHCziPrim.RealWorld)
			 GHCziPrim.Intzh
			 (GHCziPrim.Statezh GHCziPrim.RealWorld -
			  GHCziPrim.Z2H
			  (GHCziPrim.Statezh GHCziPrim.RealWorld)
			  GHCziBase.Z0T))
-


I have looked around a bit and tried to see if there is any 
documentation that says that Unit and Z0T are the same but I didn't find 
any.



Sincerely,
 Tobias

___
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


Core, implicit bindings are emitted in the wrong order

2003-01-25 Thread Tobias Gedell
The implicit bindings are emitted in the wrong order when generating Core.

It seems like the problem occurs since the implicit bindings does not 
only consist of wrappers and class functions but also conversion 
functions. These conversion functions sometimes use wrappers that have 
not yet been defined.

An example of this is found at line 240 in Base.hcr (generated with the 
-O0 flag):

-
GHCziBase.zdgfromBool ::
 GHCziBase.Bool -
 GHCziBase.ZCzpZC GHCziBase.Unit GHCziBase.Unit =
 \ (g::GHCziBase.Bool) -
  %case g %of (g1::GHCziBase.Bool)
  {
   GHCziBase.False -
GHCziBase.Inl @ GHCziBase.Unit @ GHCziBase.Unit GHCziBase.Unit;
   GHCziBase.True -
GHCziBase.Inr @ GHCziBase.Unit @ GHCziBase.Unit GHCziBase.Unit
  };
--

Here we try to use the wrappers GHCziBase.Inl and GHCziBase.Inr but they 
are defined first at line 346.


Maybe these conversion functions only use GHCziBase.ZCzpZC and then a 
possible fix would be to make sure that GHCziBase.Inl and GHCziBase.Inr 
are defined before all other implicit bindings.

Another possible fix that I have implemented is to make sure that all 
wrappers are defined before all other implicit bindings.


I have replaced line 53-70 in ghc/compiler/coreSyn/MkExternalCore.lhs with:

--
mkExternalCore :: ModGuts - C.Module
mkExternalCore (ModGuts {mg_module=this_mod, mg_types = type_env, 
mg_binds = binds})
  = C.Module mname tdefs vdefs
  where
mname  = make_mid this_mod
tdefs  = foldr collect_tdefs [] tycons
	-- Don't forget to include the implicit bindings!
vdefs  = map make_vdef (implicit_wbinds ++ implicit_binds ++ binds)
tycons = map classTyCon (typeEnvClasses type_env) ++ typeEnvTyCons 
type_env

tything = typeEnvElts type_env
implicit_wbinds = map get_defn $ concatMap implicit_wids tything
implicit_binds = map get_defn $ concatMap implicit_ids tything

-- Get only the wrappers
implicit_wids :: TyThing - [Id]
-- C.f. HscTypes.mkImplicitBinds, but we do not include constructor workers
implicit_wids (ATyCon tc) = map dataConWrapId (tyConDataCons_maybe tc 
`orElse` [])
implicit_wids other   = []

-- Get all other bindings
implicit_ids :: TyThing - [Id]
implicit_ids (ATyCon tc) = tyConSelIds tc ++ tyConGenIds tc
implicit_ids (AClass cl) = classSelIds cl
implicit_ids other   = []
--




Sincerely,
 Tobias

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


Core, shadowing type variable names

2003-01-25 Thread Tobias Gedell
There is a problem with unique type variables in some bindings when 
generating Core.

I found the error in Text/ParserCombinators/ReadP.hcr (generated with 
the -O0 flag).


The error occurs at line 825 in ReadP.hcr:

-
		%case ds %of (wild::GHCziBase.ZMZN GHCziBase.Char)
		  {GHCziBase.ZC
		   (c::GHCziBase.Char) (cs::GHCziBase.ZMZN GHCziBase.Char) -
			 zddmzgzg @ GHCziBase.Char @ (GHCziBase.ZMZN GHCziBase.Char)
			 (TextziParserCombinatorsziReadP.char c) (scan cs);
-



If we look at the definition of zddmzgzg, line 732, we see what the 
problem is:

-
   zddmzgzg :: %forall a b . (%forall b . (a -
	   TextziParserCombinatorsziReadP.P b)
	  - TextziParserCombinatorsziReadP.P b)
			 -
			 (%forall b . (b - TextziParserCombinatorsziReadP.P b) -
	  TextziParserCombinatorsziReadP.P b)
			 -
			 %forall b . (b - TextziParserCombinatorsziReadP.P b) -
	 TextziParserCombinatorsziReadP.P b = ...
-


The second time b is bound it shadows the first binding. Maybe there is 
a missing tidyType on the binding types?


If we at line 54 in ReadP.hs change
 newtype ReadP a = R (forall b . (a - P b) - P b)
to
 newtype ReadP a = R (forall z . (a - P z) - P z)
we get the correct type definition in the generated Core code:

-
   zddmzgzg :: %forall a b . (%forall zz . (a -
	TextziParserCombinatorsziReadP.P zz)
	   - TextziParserCombinatorsziReadP.P zz)
			 -
			 (%forall zz . (b - TextziParserCombinatorsziReadP.P zz) -
	   TextziParserCombinatorsziReadP.P zz)
			 -
			 %forall zz . (b - TextziParserCombinatorsziReadP.P zz) -
	  TextziParserCombinatorsziReadP.P zz = ...
-


This problem can also be found in Lex.hcr at line 1479.



Sincerely,
 Tobias

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


Invalid binding names in generated Core code

2003-01-22 Thread Tobias Gedell
The generation of binding names doesn't seem to work correctly. I have 
generated Core for Base.lhs by standing in the 
.../ghc-5.05.20030119/libraries/base directory and giving the command:

../../ghc/compiler/ghc-inplace -H16m -O -fglasgow-exts -cpp -Iinclude 
-#include HsBase.h -funbox-strict-fields -package-name base -O 
-Rghc-timing  -split-objs -O0-c GHC/Base.lhs -o GHC/Base.o  -ohi 
GHC/Base.hi



What is wrong in Base.hcr is that there are multiple bindings sharing 
the same name. I guess that this has something to do the the generation 
of unique binding names.


Here is an example, where tpl is bound multiple times, line 63 in Base.hcr:

  GHCziBase.zsze :: %forall a . GHCziBase.ZCTEq a -
a - a - GHCziBase.Bool =
\ @ a (tpl::GHCziBase.ZCTEq a) -
	%case tpl %of (tpl::GHCziBase.ZCTEq a)
	  {GHCziBase.ZCDEq
	   (tpl::a - a - GHCziBase.Bool) (tpl::a - a - GHCziBase.Bool) -
	 tpl};




Sincerely,
 Tobias

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


Re: Invalid binding names in generated Core code

2003-01-22 Thread Tobias Gedell
There was an error in my previous posting.



The generation of binding names doesn't seem to work correctly. I have 
generated Core for Base.lhs by standing in the 
.../ghc-5.05.20030119/libraries/base directory and giving the command:

../../ghc/compiler/ghc-inplace -H16m -O -fglasgow-exts -cpp -Iinclude 
-#include HsBase.h -funbox-strict-fields -package-name base -O 
-Rghc-timing  -split-objs -O0-c GHC/Base.lhs -o GHC/Base.o  -ohi 
GHC/Base.hi

I did of course also give the flag -fext-core, the correct command 
should be:

../../ghc/compiler/ghc-inplace -H16m -O -fglasgow-exts -cpp -Iinclude 
-#include HsBase.h -funbox-strict-fields -package-name base -O 
-Rghc-timing  -split-objs -O0 -fext-core-c GHC/Base.lhs -o 
GHC/Base.o  -ohi GHC/Base.hi




I apologize for the error


//Tobias

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


GHC-5.04.2 generates faulty Core code?

2003-01-19 Thread Tobias Gedell
I am currently working on my master thesis which is designing and 
implementing an usage analysis for Core. I have been working with 
ghc-5.02 but want to start use ghc-5.04.2 instead. The problem is that 
it seems like ghc-5.04.2 generates faulty Core code.

I need to generate Core for the entire prelude and parts of the hslibs 
modules.

What I do is:

ghc -fno-implicit-prelude -fno-code -cpp -fext-core -fglasgow-exts Base.lhs


Then I try to analyse Base.hcr using my own program. I then get an error:

Base.hcr:1261:
Invalid variable name in getCoreType, (Just GHCziBase,zeze)


This occurs since my program cannot find the type for GHCziBase.zeze 
which is refered to at line 1261 in Base.hcr.

If I look at that line in Base.hcr I find:

GHCziBase.zaza (GHCziBase.zeze @ a zddEq x y) (zeze5 xs ys)};


But there is no definition for GHCziBase.zeze in the file Base.hcr. It 
seems to me that GHC generates faulty Core code.

Am I doing something wrong? Should I try to use another version of GHC?


Thankful for help

Sincerely,
 Tobias

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