RnIfaces.lhs:931: Non-exhaustive patterns in case

1999-12-14 Thread Ilya Beylin

A very cryptic error message, probably referring to the source code of ghc itself.
It was caused by an empty *.hi for an imported module which happened to be in the 
working directory.
Side remark: if ghc still has run-time errors, why doesn't it decorate them
to make obvously different from the compile errors?
May sound silly, but my first thought was "Cool! ghc warns about incomplete
cases", and then it took me a while to realise that there is no RnIfaces.lhs
anywhere in my filesystem :)

Regards,
Ilya Beylin

The verbose output follows:
---
The Glorious Glasgow Haskell Compilation System, version 4.04, patchlevel 1

Effective command line: -v -c

Ineffective C pre-processor:
echo '{-# LINE 1 "Typechecking.hs" -}'  /tmp/ghc15352.cpp  cat 
Typechecking.hs  /tmp/ghc15352.cpp

real0.0
user0.0
sys 0.0
ghc:compile:Output file Typechecking.o doesn't exist
ghc:compile:Interface file Typechecking.hi doesn't exist
ghc:recompile:Input file Typechecking.hs newer than Typechecking.o

Haskell compiler:
/usr/pd/ghc-4.04/lib/ghc-4.04/hsc /tmp/ghc15352.cpp  
-fignore-interface-pragmas -fomit-interface-pragmas -fsimplify [ -finline-phase2 
-fmax-simplifier-iterations4 ]   -fwarn-overlapping-patterns -fwarn-missing-methods 
-fwarn-duplicate-exports 
 -fhi-version=404 -static -himap=.%.hi:/usr/pd/ghc-4.04/lib/ghc-4.04/imports/std%.hi   
 -v -hifile=/tmp/ghc15352.hi -C=/tmp/ghc15352.hc -F=/tmp/ghc15352_stb.c 
-FH=/tmp/ghc15352_stb.h +RTS -H600 -K100
Glasgow Haskell Compiler, version 4.04, for Haskell 98, compiled by GHC version 4.04

RnIfaces.lhs:931: Non-exhaustive patterns in case



real1.4
user1.1
sys 0.2
deleting... /tmp/ghc15352.cpp /tmp/ghc15352.hi /tmp/ghc15352.hc /tmp/ghc15352_stb.c 
/tmp/ghc15352_stb.h

rm -f /tmp/ghc15352*



infix constructor in a pattern

1999-12-14 Thread Ilya Beylin

The following code is accepted by hugs and hbc, but produces an error in ghc-4.04-1

-
module Bug where
infix 5 |- 
infix 9 :=

data Equal = Char := Int

(|-) :: Int - Equal - Bool
0 |-  x:=y  = 1 |- x:=y
2 |- (x:=y) = 0 |- x:=y
_ |-  _ = False  
-
Bug.hs:8:
`|-' is not a data constructor
In the pattern: 0 |- x := y

Compilation had errors
-
As one can guess,  0 |-  x:=y  is parsed
correctly as  0 |- (x:=y) when on left hand side,
but not on the right hand side.




RE: infix constructor in a pattern

1999-12-14 Thread Simon Marlow

 The following code is accepted by hugs and hbc, but produces 
 an error in ghc-4.04-1
 
 -
 module Bug where
 infix 5 |- 
 infix 9 :=
 
 data Equal = Char := Int
 
 (|-) :: Int - Equal - Bool
 0 |-  x:=y  = 1 |- x:=y
 2 |- (x:=y) = 0 |- x:=y
 _ |-  _ = False  
 -
 Bug.hs:8:
 `|-' is not a data constructor
 In the pattern: 0 |- x := y
 
 Compilation had errors
 -
 As one can guess,  0 |-  x:=y  is parsed
 correctly as  0 |- (x:=y) when on left hand side,
 but not on the right hand side.

Actually the other way around: it's ok on the right, but not on the left.
This is indeed a bug in GHC, but I don't think we'll fix it, at least not in
the near future.

The reason is that to correctly parse these left-hand-sides means knowing
all the fixity info, which can't be known until the whole file has been
parsed and all the interface files have been read.  This means deferring
some things which we currently do during parsing (like grouping the
equations by name) until much later.  Incedentally, there are several other
fixity-related examples that GHC gets wrong (and Hugs, HBC and NHC for that
matter).

Workaround: use explicit parentheses on the left hand side.  Thanks for the
report.

Cheers,
Simon



RE: 4.04 posix/AF_UNIX lossage

1999-12-14 Thread Simon Marlow

 when attempting to bootstrap under netbsd-current:
 
 ==fptools== gmake all -r;
  in /orb/s/netbsd/usr/pkgsrc/lang/ghc/work.i386/fptools/ghc/lib/misc
 --
 --
 rm -f CString.o ; if [ ! -d CString ]; then mkdir CString; 
 else find CString -name '*.o' -print | xargs rm -f __rm_food ; fi ;
 ../../../ghc/driver/ghc -i../concurrent:../posix -recomp -cpp 
 -fglasgow-exts -fvia-C -Rghc-timing -O -split-objs -odir 
 CString -static-c CString.lhs -o CString.o -osuf o
 ghc: 90101184 bytes, 52 GCs, 2037934/3905668 avg/max bytes 
 residency (4 samples), 10M in use, 0.00 INIT (0.00 elapsed), 
 2.22 MUT (2.51 elapsed), 0.97 GC (0.96 elapsed) :ghc
 ghc: module version unchanged at 1
 touch CString.o ;
 rm -f SocketPrim.o ; if [ ! -d SocketPrim ]; then mkdir 
 SocketPrim; else find SocketPrim -name '*.o' -print | xargs 
 rm -f __rm_food ; fi ;
 ../../../ghc/driver/ghc -i../concurrent:../posix -recomp -cpp 
 -fglasgow-exts -fvia-C -Rghc-timing -O -split-objs -odir 
 SocketPrim -static  -I../std/cbits -H12m 
 -optc-DNON_POSIX_SOURCE  -c SocketPrim.lhs -o SocketPrim.o -osuf o
 
 SocketPrim.lhs:14: Variable not in scope: `packSocketType'
[ etc. ]

Thanks for the report.  I haven't tried building GHC on a NetBSD box (and I
don't have one to hand), so you'll have to help us debug this one.  I assume
you're trying to build lang/ghc from the FreeBSD ports tree?  

A good first approximation is probably to go through SocketPrim.lhs and add
netbsd_TARGET_OS to all the #ifdefs with freebsd[23]_TARGET_OS in them.

BTW, the ports tree version will only work with x86 at the moment.

Cheers,
Simon



Re: 4.04 posix/AF_UNIX lossage

1999-12-14 Thread Julian Assange


Hi Simon, I eventually managed to produce an executable (but see
below) with the following patches (note that the address family
enumeration below is *not* identical to freebsd):

$NetBSD$

--- ghc/lib/misc/SocketPrim.lhs Wed Sep 15 09:06:26 1999
+++ ghc/lib/misc/SocketPrim.lhs Tue Dec 14 13:00:08 1999
@@ -941,10 +941,56 @@

 #endif

+#if netbsd_TARGET_OS || netbsd_elf_TARGET_OS
+
+data Family =
+   AF_UNSPEC   -- unspecified
+  |AF_UNIX -- local to host (pipes, portals)
+  |AF_INET -- internetwork: UDP, TCP, etc.
+  |AF_IMPLINK  -- arpanet imp addresses
+  |AF_PUP  -- pup protocols: e.g. BSP
+  |AF_CHAOS-- mit CHAOS protocols
+  |AF_NS   -- XEROX NS protocols
+  |AF_ISO  -- ISO protocols
+--|AF_OSI is the same as AF_ISO
+  |AF_ECMA -- european computer manufacturers
+  |AF_DATAKIT  -- datakit protocols
+  |AF_CCITT-- CCITT protocols, X.25 etc
+  |AF_SNA  -- IBM SNA
+  | AF_DECnet  -- DECnet
+  | AF_DLI -- DEC Direct data link interface
+  | AF_LAT -- LAT
+  |AF_HYLINK   -- NSC Hyperchannel
+  |AF_APPLETALK-- Apple Talk
+  |AF_ROUTE-- Internal Routing Protocol
+  |AF_LINK -- Link layer interface
+  |Pseudo_AF_XTP   -- eXpress Transfer Protocol (no AF)
+  | AF_COIP -- connection-oriented IP, aka ST II
+  | AF_CNT -- Computer Network Technology
+  | Psuedo_AF_RTIP  -- Help Identify RTIP packets
+  | AF_IPX -- Novell Internet Protocol
+  | AF_INET6   -- IPv6
+  | Pseudo_AF_PIP   -- Help Identify PIP packets
+  | AF_ISDN -- Integrated Services Digital Network
+--| AF_E164is the same as AF_ISDN
+  | AF_NATM-- native ATM access
+  | AF_ARP -- (rev.) addr. res. prot. (RFC 826)
+  | Pseudo_AF_KEY   -- Internal key-management function
+  | Pseudo_AF_HDRCMPLT -- Used by BPF to not rewrite hdrs in iface output
+  | AF_MAX
+   deriving (Eq, Ord, Ix, Show)
+
+packFamily = index (AF_UNSPEC, AF_MAX)
+unpackFamily family = (range (AF_UNSPEC, AF_MAX))!!family
+
+#endif
+
+
 -- Alpha running OSF or a SPARC with SunOS, rather than Solaris.

 #if osf1_TARGET_OS || osf3_TARGET_OS || sunos4_TARGET_OS || hpux_TARGET_OS || \
-   aix_TARGET_OS || freebsd2_TARGET_OS || freebsd3_TARGET_OS
+   aix_TARGET_OS || freebsd2_TARGET_OS || freebsd3_TARGET_OS || \
+   netbsd_TARGET_OS || netbsd_elf_TARGET_OS
 data SocketType =
  Stream
| Datagram
diff -u -r old/fptools/ghc/rts/MBlock.c work.i386/fptools/ghc/rts/MBlock.c
$NetBSD$

--- ghc/rts/MBlock.cWed Sep 15 09:06:54 1999
+++ ghc/rts/MBlock.cTue Dec 14 10:27:15 1999
@@ -47,6 +47,10 @@
  */
 #define ASK_FOR_MEM_AT 0x5000

+#elif netbsd_TARGET_OS
+/* NetBSD i386 shared libs are at 0x4000
+ */
+#define ASK_FOR_MEM_AT 0x5000
 #elif linux_TARGET_OS
 /* Any ideas?
  */
$NetBSD$

--- ghc/driver/ghc-asm.lprl Wed Sep 15 09:05:45 1999
+++ ghc/driver/ghc-asm.lprl Tue Dec 14 22:09:04 1999
@@ -104,7 +104,7 @@
 $T_HDR_direct   = "\t.SPACE \$TEXT\$\n\t.SUBSPA \$CODE\$\n\t\.align 4\n";

 ##
-} elsif ( $TargetPlatform =~ 
/^i386-.*-(linuxaout|freebsd2|nextstep3|cygwin32|mingw32)$/ ) {
+} elsif ( $TargetPlatform =~ 
+/^i386-.*-(linuxaout|freebsd2|netbsd|nextstep3|cygwin32|mingw32)$/ ) {
# NeXT added but not tested. CaS

 $T_STABBY  = 1; # 1 iff .stab things (usually if a.out format)
@@ -135,12 +135,12 @@
 $T_HDR_direct   = "\.text\n\t\.align 2,0x90\n";

 ##
-} elsif ( $TargetPlatform =~ /^i386-.*-(solaris2|linux|freebsd3)$/ ) {
+} elsif ( $TargetPlatform =~ /^i386-.*-(solaris2|linux|freebsd3|netbsd_elf)$/ ) {

 $T_STABBY  = 0; # 1 iff .stab things (usually if a.out format)
 $T_US  = ''; # _ if symbols have an underscore on the front
 $T_PRE_APP = # regexp that says what comes before APP/NO_APP
- ($TargetPlatform =~ /-(linux|freebsd3)$/) ? '#' : '/' ;
+ ($TargetPlatform =~ /-(linux|freebsd3|netbsd_elf)$/) ? '#' : '/' 
+;
 $T_CONST_LBL= '^\.LC(\d+):$'; # regexp for what such a lbl looks like
 $T_POST_LBL= ':';
 $T_X86_PRE_LLBL_PAT = '\.L';
@@ -150,7 +150,7 @@
 $T_MOVE_DIRVS   = 
'^(\s*(\.(p2)?align\s+\d+(,0x90)?|\.globl\s+\S+|\.text|\.data|\.section\s+.*|\.type\s+.*|\.Lfe.*\n\t\.size\s+.*|\.size\s+.*|\.ident.*)\n)';
 $T_COPY_DIRVS   = '\.(globl)';

-if ( $TargetPlatform =~ /freebsd3/ ) {
+if ( $TargetPlatform =~ /freebsd3|netbsd_elf/ ) {
 $T_hsc_cc_PAT   = '\.ascii.*\)(hsc|cc) 

Makefile typos

1999-12-14 Thread Julian Assange


--- /p/lang/ghc/old/fptools/MakefileWed Sep 15 09:03:33 1999
+++ MakefileWed Dec 15 16:04:58 1999
@@ -15,7 +15,7 @@
 # on whether we do `make install' or not. Having a $(ifeq ... ) would
 # be preferable..
 CURRENT_TARGET = $(MAKECMDGOALS)
-SUBDIRS = $(shell if (test x$(CURRENT_TARGET) = xinstall) ; then echo 
$(ProjectsToInstall); else echo $(ProjectsToBuild); fi)
+SUBDIRS = $(shell if test x$(CURRENT_TARGET) = xinstall) ; then echo 
+$(ProjectsToInstall); else echo $(ProjectsToBuild); fi)

 ifneq "$(Project)" ""
include $(shell echo $(Project) | tr A-Z a-z)/mk/config.mk



CL2000: final call for workshop proposals

1999-12-14 Thread Raamsdonk van F

*** apologies for multiple copies ***

CL2000
   
First International Conference on Computational Logic
Imperial College, London, UK, 24th to 28th July, 2000
   http://www.doc.ic.ac.uk/cl2000/

  FINAL CALL FOR WORKSHOP PROPOSALS
DEADLINE: DECEMBER 20


*   NEW! CHANGE OF DATE AND POLICY: WORKSHOPS OF CL2000 WILL BE HELD*
*   DURING THE CONFERENCE, BETWEEN JULY 24 AND 28, 2000. WORKSHOPS WILL *
*   NOT BE POST-CONFERENCE ACTIVITIES, BUT CENTRAL EVENTS OF CL2000.*
*   Organizers wishing to have their workshop after the conference on   *
*   July 29, should contact the workshop coordinator for a special  *
*   arrangement.*


CL2000 is the first conference in a major new series of annual
international conferences bringing together the various communities of
researchers who have a common interest in Computational Logic.

CL2000 includes seven streams covering various subfields of
computational logic. DOOD2000 (6th International Conference on Rules
and Objects in Databases) and LOPSTR2000 (10th International Workshop
on Logic-based Program Synthesis and Transformation) will be streams
within CL2000. Moreover, the International Conference on Logic
Programming (ICLP) is now integrated into CL2000.  ILP2000 (10th
International Conference on Inductive Logic Programming) is also
collocated with CL2000.

The organisation of CL2000 will provide facilities for half-day and
one-day workshops, to be held during the conference, between July 24
and 28, 2000. Organizers that wish to organize their workshop after
the conference on July 29, should contact the workshop coordinator for
a special arrangement.

Researchers and practitioners are invited to submit proposals for
workshops on topics in computational logic.

Anyone wishing to organise a workshop should send (possibly by email,
in text or html format) a proposal no longer than two pages to the
workshop coordinator by *** DECEMBER 20, 1999 ***.  
The proposal should describe the topic of the proposed workshop and 
its relevance to computational logic. Besides the contact information 
and the list of the organisers, the proposal should contain - when 
applicable - the following information:

- proposed duration of the workshop (half day/one day),
- description of previously organised similar workshops, 
- expected number of participants,
- character of the workshop (formal/informal, 
  via submission/invitation),
- plans for publication of the proceedings.

The workshop organisers will be responsible for maintaining a
homepage, and for producing one hard copy of the proceedings in A4 or
US-letter format. Organisers who wish to use a format different than
A4 or US-letter are expected to produce the needed copies of
proceedings as well.

Proposals will be evaluated by the program committee and decisions
will be made by January 10, 2000. Further information about the
arrangements for workshops can be obtained from the workshop
coordinator.

Workshop Coordinator: 

Sandro Etalle, 
email: [EMAIL PROTECTED]
Dept. of Computer Science, 
University of Maastricht, 
P.O. Box 616, 6200 MD Maastricht 
Phone: ++31 (0)6 23250328
Fax:   ++31 (0)43 3884897





Singletons and Reflection

1999-12-14 Thread Chris Angus

Hi,
 
What do folk out there think to the idea of having a std module
in Haskell which contains dynamic environment info.
 
things I mean are
 
progName :: String
args:: String
 
and maybe funs like
 
getProperties :: FileName - PropertyLookup
 
(obviously this getProperties fn whould have to memoise the file contents
to preserve referential transparency).
 
This would be an alternative to definitions like
 
installationRoot = "/usr/local/"
 
instead we could write
 
installationRoot = lookup "IROOT" Globals.env
 
 
Also I was thinking that other modules could "export" values as being
reflective and the compiled code could register these values
at load-time into a list
 
reflections :: [(FullyQualifiedName,Dynamic)]
 
and values could be requested from it a la...
 
lookup :: a - Name - Maybe a
 
Where the initial "a" is needed to make it all typesafe 
 
If we had this we could implement additive code
 
i.e. rather than
 
myImageReader :: String - IO Image
myImageReader name
= case (getExtension name) of
BMP - Bmp.readBmp name
JMG - Jpg.readJpg name
_  - error "unknown type"
 
we could implement
 
myImageReader :: String - IO Image
myImageReader name
= case (Reflect.lookup (bot::String - IO Image) (makeFnName name) Just
f  - f name
Nothing - error "unknown type"
 
i.e. passing "myfile.bmp" to makeFnName gives
"Bmp.readBmp"
and passing "x.yz" to it gives
"Yz.readYz"
 
since the list of reflections is built at load time we can extend this
functionality by simply linking extra modules with it
 
i.e.
 
main.o can read no file types
main.o + bmp.o can read bitmaps
main.o + bmp.o + jpg.o can read bmps and jpgs
 
i.e. we do not have to exit case statements and extend types to
add extra functionality
 
in Bmp.hs say we could have
 
module Bmp where
import Image
 
reflect readBmp
 
readBmp :: String - IO Image
...
 
which would get munged to
 
module Bmp where
import Image
 
-- This gets appended to the global reflection list at load time --
[("Bmp.readBmp",toDynamic readBmp)]
 
readBmp :: String - IO Image
...
 
 
All of this means that the meaning of the code is not the following 
 
eval main userAndLibraryDefs
 
but the following
 
eval main (userAndLibraryDefs + LoadTimeDefs)
 
and we still have ref. transparency
 
Comments / Flames ?
 
 
 
Chris