The program shown below elicits a complaint about pattern overlap for
doMem1 (but not doMem2).  I don't expect any complaint.  (Hugs accepts
both.)

Dean Herington
[EMAIL PROTECTED]


swift(125)% cat GHCtest1.lhs
> module Main where

> type Label = Int

> data Exp = CONST Integer
>          | LREF Label
>          | NUMOP Numop Exp Exp

> data Numop = ADD | SUB | MUL | DIV

> doMem1 :: Exp -> Int
> doMem1 (NUMOP ADD e1 (CONST i)) = 1
> doMem1 (NUMOP ADD (CONST i) e2) = 2
> doMem1 (NUMOP SUB e1 (CONST i)) = 3
> doMem1 (NUMOP ADD (LREF lab) (CONST i)) = 4
> doMem1 (NUMOP ADD (CONST i) (LREF lab)) = 5
> doMem1 (NUMOP SUB (LREF lab) (CONST i)) = 6

> doMem2 :: Exp -> Int
> doMem2 (NUMOP ADD (LREF lab) (CONST i)) = 4
> doMem2 (NUMOP ADD (CONST i) (LREF lab)) = 5
> doMem2 (NUMOP SUB (LREF lab) (CONST i)) = 6


> main :: IO ()
> main = return ()


swift(121)% cat /etc/motd
Sun Microsystems Inc.   SunOS 5.7       Generic October 1998
swift(122)% uname -a
SunOS swift.cs.unc.edu 5.7 Generic_106541-11 sun4u sparc SUNW,Ultra-2
swift(123)% gcc -v
Reading specs from
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/specs
gcc version 2.95.2 19991024 (release)
swift(126)% ghc -v GHCtest1.lhs
The Glorious Glasgow Haskell Compilation System, version 4.08.1

literate pre-processor:

/afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2/unlit
GHCtest1.lhs -  >> /tmp/ghc16125.lpp

real        0.0
user        0.0
sys         0.0

Effective command line: -v

Ineffective C pre-processor:
        echo '{-# LINE 1 "GHCtest1.lhs" -}' > /tmp/ghc16125.cpp && cat
/tmp/ghc16125.lpp >> /tmp/ghc16125.cpp

real        0.0
user        0.0
sys         0.0
ghc:compile:Interface file GHCtest1.hi doesn't exist

Haskell compiler:

/afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2/hsc
/tmp/ghc16125.cpp  -fignore-interface-pragmas -fomit-interface-pragmas
-fsimplify [ -fmax-simplifier-iterations4 ]
-fwarn-overlapping-patterns -fwarn-missing-methods -fwarn-missing-fields
-fwarn-deprecations -fwarn-duplicate-exports -fhi-version=408 -static
"-himap=.%.hi:/afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2/imports/std%.hi"
"-himap-sep=:"    -v -hifile=/tmp/ghc16125.hi -olang=C
-ofile=/tmp/ghc16125.hc -F=/tmp/ghc16125_stb.c -FH=/tmp/ghc16125_stb.h
+RTS -H6000000 -K1000000
Glasgow Haskell Compiler, version 4.08, for Haskell 98, compiled by GHC
version 4.08

GHCtest1.lhs:13: Pattern match(es) are overlapped in the definition of
function `doMem1':
            doMem1 (NUMOP ADD (LREF lab) (CONST i)) = ...
            doMem1 (NUMOP ADD (CONST i) (LREF lab)) = ...
            doMem1 (NUMOP SUB (LREF lab) (CONST i)) = ...

real        8.0
user        1.9
sys         0.1

Pin on Haskell consistency info:
        echo 'static char ghc_hsc_ID[] = "@(#)hsc GHCtest1.lhs
40.0,,";' >> /tmp/ghc16125.hc

real        0.0
user        0.0
sys         0.0
*** New hi file follows...
__interface "Main" Main  where
__export Main main;
import PrelFloat 1 !;
import Prelude 1;
type Label = PrelBase.Int ;
data Exp = CONST PrelNum.Integer |  LREF Label |  NUMOP Numop Exp Exp ;
data Numop = ADD |  SUB |  MUL |  DIV ;
main :: PrelIOBase.IO PrelBase.Z0T ;


ghc: module version unchanged at 6

Replace .hi file, if changed:
        cmp -s Main.hi /tmp/ghc16125.hi-new || ( rm -f Main.hi && cp
/tmp/ghc16125.hi-new Main.hi )

real        0.6
user        0.0
sys         0.0

C compiler:
        gcc -v  -S -Wimplicit -O    -I.
-I/afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2/includes
ghc16125.c > /tmp/ghc16125.ccout 2>&1 && ( if [ ghc16125.s !=
/tmp/ghc16125_o.s ] ; then mv ghc16125.s /tmp/ghc16125_o.s ; else exit 0
; fi )
Reading specs from
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/specs
gcc version 2.95.2 19991024 (release)
 /afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/cpp
-lang-c -v -I.
-I/afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2/includes
-D__GNUC__=2 -D__GNUC_MINOR__=95 -Dsparc -Dsun -Dunix -D__svr4__
-D__SVR4 -D__sparc__ -D__sun__ -D__unix__ -D__svr4__ -D__SVR4 -D__sparc
-D__sun -D__unix -Asystem(unix) -Asystem(svr4) -D__OPTIMIZE__ -Wimplicit
-D__GCC_NEW_VARARGS__ -Acpu(sparc) -Amachine(sparc) ghc16125.c
/tmp/cctFRT9v.i
GNU CPP version 2.95.2 19991024 (release) (sparc)
#include "..." search starts here:
#include <...> search starts here:
 .
 /afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2/includes

 /afs/isis/pkg/gcc-2952/include
 
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/../../../../sparc-sun-solaris2.7/include

 /afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/include
 /usr/include
End of search list.
The following default directories have been omitted from the search
path:
 
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/../../../../include/g++-3

End of omitted list.
 /afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/cc1
/tmp/cctFRT9v.i -quiet -dumpbase ghc16125.c -O -Wimplicit -version -o
ghc16125.s
GNU C version 2.95.2 19991024 (release) (sparc-sun-solaris2.7) compiled
by GNU C version 2.8.1.

real        4.2
user        0.7
sys         0.1

Unix assembler:
        gcc -o GHCtest1.o -c  -I.
-I/afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2/includes
/tmp/ghc16125.s

real        0.1
user        0.0
sys         0.0

Linker:
        gcc -v -u PrelMain_mainIO_closure -u PrelBase_Izh_static_info -u
PrelBase_Czh_static_info -u PrelFloat_Fzh_static_info -u
PrelFloat_Dzh_static_info -u PrelAddr_Azh_static_info -u
PrelAddr_Wzh_static_info -u PrelAddr_I64zh_static_info -u
PrelAddr_W64zh_static_info -u PrelStable_StablePtr_static_info -u
PrelBase_Izh_con_info -u PrelBase_Czh_con_info -u PrelFloat_Fzh_con_info
-u PrelFloat_Dzh_con_info -u PrelAddr_Azh_con_info -u
PrelAddr_Wzh_con_info -u PrelAddr_I64zh_con_info -u
PrelAddr_W64zh_con_info -u PrelStable_StablePtr_con_info -u
PrelBase_False_closure -u PrelBase_True_closure -u
PrelPack_unpackCString_closure -u PrelException_stackOverflow_closure -u
PrelException_heapOverflow_closure -u
PrelException_NonTermination_closure -u
PrelException_PutFullMVar_closure -u
PrelException_BlockedOnDeadMVar_closure -u __init_Prelude -u
__init_PrelMain  GHCtest1.o
-L/afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2
-lHSstd -lHSstd_cbits -lHSrts -lgmp -lm
Reading specs from
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/specs
gcc version 2.95.2 19991024 (release)
 /afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/collect2
-V -Y P,/usr/ccs/lib:/usr/lib -Qy -u PrelMain_mainIO_closure -u
PrelBase_Izh_static_info -u PrelBase_Czh_static_info -u
PrelFloat_Fzh_static_info -u PrelFloat_Dzh_static_info -u
PrelAddr_Azh_static_info -u PrelAddr_Wzh_static_info -u
PrelAddr_I64zh_static_info -u PrelAddr_W64zh_static_info -u
PrelStable_StablePtr_static_info -u PrelBase_Izh_con_info -u
PrelBase_Czh_con_info -u PrelFloat_Fzh_con_info -u
PrelFloat_Dzh_con_info -u PrelAddr_Azh_con_info -u PrelAddr_Wzh_con_info
-u PrelAddr_I64zh_con_info -u PrelAddr_W64zh_con_info -u
PrelStable_StablePtr_con_info -u PrelBase_False_closure -u
PrelBase_True_closure -u PrelPack_unpackCString_closure -u
PrelException_stackOverflow_closure -u
PrelException_heapOverflow_closure -u
PrelException_NonTermination_closure -u
PrelException_PutFullMVar_closure -u
PrelException_BlockedOnDeadMVar_closure -u __init_Prelude -u
__init_PrelMain
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/crt1.o
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/crti.o
/usr/ccs/lib/values-Xa.o
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/crtbegin.o
-L/afs/cs.unc.edu/home/heringto/applications/ghc-4.08.1/lib/sparc-sun-solaris2
-L/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2
-L/usr/ccs/bin -L/usr/ccs/lib -L/afs/isis/pkg/gcc-2952/lib GHCtest1.o
-lHSstd -lHSstd_cbits -lHSrts -lgmp -lm -lgcc -lc -lgcc
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/crtend.o
/afs/isis/pkg/gcc-2952/lib/gcc-lib/sparc-sun-solaris2.7/2.95.2/crtn.o
ld: Software Generation Utilities - Solaris-ELF (4.0)

real        3.6
user        0.8
sys         0.1

rm -f /tmp/ghc16125*
swift(127)%


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

Reply via email to