1)

I have 3 directories:
c:\temp\imports, c:\temp\objs and c:\temp\tst.
Current directory is c:\temp. Directory c:\temp\tst
contains 2 files: Main.hs and Ex.hs. Main.hs import
Ex.hs

I compile with
ghc tst\Main.hs -itst --make -odir objs -hidir imports
-o main.exe

ghc raise error:
FATAL: Can't create objs\tst\Main.o: No such file or
directory

I think that objs\tst\Main.o must be objs\Main.o
Ex.hs compiled to objs\Ex.o

2)

ghc-pkg with option -a and maybe with -r produces
package.conf.old. In the second when I use "ghc-pkg
-a"
it raises "Fail: already exists", because
package.conf.old already exists.


3)

When compile these examples with option --make, ghc
raises error:
   Test.hs:9: Foo Int
   ./Test.hi-boot:8: Foo Int

file Test2.hs:

module Test2 where

   import {-# SOURCE #-} Test

   tst x = show x

   fun = "??" ++ f (0 :: Int)

file Test:

module Test where

   import Test2

   class Foo a where
      f :: a -> String


   instance Foo Int where
      f = tst

file Test.hi-boot:

__interface "Main" Test 1 502 where
__export  Test Foo{f};
import PrelBase ! :: 1;
import PrelShow :: 1;
;
instance {Foo PrelBase.Int} = zdfFooInt ;
class Foo a where { f :: a -> PrelBase.String; };
zdfFooInt :: {Foo PrelBase.Int};



I found these bugs when I porting Clean ObjectIO to
ghc-5.02. Bug fixes allow me complete port.


__________________________________________________
Do You Yahoo!?
NEW from Yahoo! GeoCities - quick and easy web site hosting, just $8.95/month.
http://geocities.yahoo.com/ps/info1

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

Reply via email to