Dear GHC team,

I have tested (on somewhat 90%) the  cvs ghc-6-2-branch  of May 24.
It looks almost correct for DoCon.
Still I pretend to report the two bugs, so far.

1: (wrote earlier) is on negative number of bytes shown by 
   `:set +s'.
2: follows below, it also contains questions about organizing a 
   package.

Thank you in advance for the help,

-----------------
Serge Mechveliani
[EMAIL PROTECTED]



--------------------------------------------------------------
Having  docon-2.08-pre,  build it under  -O  as  install.txt  
specifies.

And I write in DoCon Manual how to organize a package for the user
example program which links DoCon library and package.

1. 
After installing DoCon, set the variables

  setenv doconc    ".../docon/source/docon.conf"
  setenv pcdocon   "-package-conf ${doconc}"
  setenv pcpdocon  "${pcdocon} -package docon"

2. 
Design  Makefile  for creating a user package  foo  
by compiling the modules
                           u/Root.hs
                           u/subdir/M.hs

and putting the interfaces and libraries to the directory  u/lib/

Let the module  Root  import some entities from  DoCon  and from the 
module  M.

  ------------------------------------------------------------------
  module Root where                            -- in file  u/Root.hs

  import DExport   -- imports all entities of DoCon and many of GHC
  import M (m)     -- of the user project

  f = (m,m)

  intRoot :: Z -> Maybe Z
  intRoot    n =  let  (ps,exps) = unzip $ factor n
                  in
                  if  any (not . even) exps  then  Nothing
                  else
                    let  halfs = map (`quot` 2) exps
                    in
                    Just $ product $ zipWith power ps halfs

  ------------------------------------------------------------------
  module M where  m = True                    -- file  u/subdir/M.hs
  ------------------------------------------------------------------



-- The  Makefile  in the directory  u/  should be  ------------------

ghcBinDir = /home/mechvel/ghcCVS/inst/bin
#
# EDIT these four!  
# $(doconc)  is the path to the DoCon configuration file,
# $(s)       is the user source directory,
# $(e)       a directory the user library and interface to install to.
#
doconc = /home/mechvel/docon/2.08/docon/source/docon.conf
s      = /home/mechvel/t/u
e      = $(s)/lib

ghc    = $(ghcBinDir)/ghc
ghcpkg = $(ghcBinDir)/ghc-pkg

pcdocon  = -package-conf $(doconc)
pcpdocon = $(pcdocon) -package docon

RANLIB   = ar -s
language = -fglasgow-exts  -fallow-overlapping-instances \
                           -fallow-undecidable-instances

warnings = -fno-warn-overlapping-patterns -fwarn-unused-binds \
            -fwarn-unused-matches -fwarn-unused-imports 
idirs    = subdir
HCFlags  =  $(language) $(warnings)                            \
            -i$(idirs) -odir $(e) -hidir $(e)  -ddump-hi-diffs \
            +RTS $(space) -RTS  $(extraHCOpts) 

space       = -M55m
extraHCOpts =
#             -O    ghcpkg=... 

pack =Package {name            = "\"foo\"",  \
               import_dirs     = ["\"$(e)\""],    \
               source_dirs     = [],              \
               library_dirs    = ["\"$(e)\""],    \
               hs_libraries    = ["\"HSfoo\""], \
               extra_libraries = [], \
               include_dirs    = [], \
               c_includes      = [], \
               package_deps    = [], \                    -- ?
               extra_ghc_opts  = [$(extraPackOpts)], \
               extra_cc_opts   = [],                 \
               extra_ld_opts   = [] } 

extraPackOpts = $(pwarnings), $(planguage)

# `backslash' copy of $(HCFlags)  
#
planguage = "\"-fglasgow-exts\"", \
            "\"-fallow-overlapping-instances\"", \
            "\"-fallow-undecidable-instances\""
pwarnings = "\"-fno-warn-overlapping-patterns\"", \
            "\"-fwarn-unused-binds\"","\"-fwarn-unused-matches\"", \
            "\"-fwarn-unused-imports\""

obj:
        if [ ! -d $(e) ]; then mkdir $(e); fi
        $(ghc) $(HCFlags) $(pcpdocon) --make Root  -package-name foo

foo:    obj
        rm -f  $(e)/libHSfoo.a $(e)/HSfoo.o
        ar -qc $(e)/libHSfoo.a $(wildcard $(e)/*.o)
        $(RANLIB)  $(e)/libHSfoo.a
        echo $(pack) | $(ghcpkg) -f $(s)/foo.conf -u -g
        $(ghcpkg) -f $(s)/foo.conf -l
#
# o. files can be extracted from the library by  ar -x 

clear:
        $(ghcpkg) -f $(s)/foo.conf -r foo
        rm -f  $(s)/foo.conf.old
        rm -rf $(e)
--------------------------------------------------------------------

Questions:
*  should it be set   package_deps = ["\"docon\""]
   ?
   (it does not work)

* how to avoid above the ugly  "backslash copy of $(HCFlags)" ?  

* are the goals  obj, foo  done correct ?


Making  foo:      cd  .../u
                  make foo
 
Similarly as for DoCon package, arrange the variables

  setenv fooc    "/home/mechvel/t/u/foo.conf"
  setenv pcfoo   "-package-conf ${fooc}"
  setenv pcpfoo  "${pcfoo} -package foo"

To run  intRoot  from the separate directory, say  foo,  command 

  cd  .../foo
  ghci $pcpfoo $pcpdocon
 
  Loading package base ... linking ... done.
  ...
  Loading package docon ... linking ... done.
  Loading package foo ... linking ... done.
  
  Prelude> Root.intRoot 16
  Just 4


But the users will often try to run it from the source directory
(just forgetting to leave it, as I do):

  cd .../u/t
  ghci $pcpfoo $pcpdocon
 
  Loading package base ... linking ... done.
  ...
  Loading package data ... linking ... done.
  Loading package docon ... linking ... done.
  Loading package foo ... linking ... done.
  
  Prelude> :m Root

   Failed to load interface for `Root':
    Bad interface file: ./Root.hi
    ./Root.hi: openBinaryFile: does not exist (No such file or directory)

  Prelude> Root.intRoot 16

   <interactive>:1:
    Failed to load interface for `Root':
        Bad interface file: ./Root.hi
          ./Root.hi: openBinaryFile: does not exist
             (No such file or directory)

   <interactive>:1: Variable not in scope: `Root.intRoot'


Now, if we apply first  > Root.intRoot 16
                        > Just 4
  
and then                > :m Root
,
then it starts to work.

As I recall, there was some hindrance with  :m Root 
when  Root.hs  is in the current directory and also  Root  
is in the linked library.
But the GHC reaction at this point is misleading and frightening.
At least, could it report something explanatory?






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

Reply via email to