[jhc] For "signum (...::Word)", jhc/gcc reports "error: duplicate case value"

John Meacham john at repetae.net
Fri Dec 5 23:14:57 UTC 2014


Hmm.. yikes. that is a real bug. I'll see if i can reproduce it.

    John

On Fri, Dec 5, 2014 at 5:46 AM, Thorkil Naur <naur at post11.tele.dk> wrote:
> Hello jhc,
>
> Using
>
>   $ uname -a
>   Linux tn24 3.13.0-39-generic #66-Ubuntu SMP Tue Oct 28 13:31:23 UTC 2014 i686 i686 i686 GNU/Linux
>   $ ghc --version
>   The Glorious Glasgow Haskell Compilation System, version 7.4.2
>   $ jhc --version
>   jhc 0.8.2 (mydniquipepo-32)
>   compiled by ghc-7.4 on a i386 running linux
>   $
>
> and with
>
>   $ cat Signum1.hs
>   import Data.Word
>   s = "-47"
>   main = do
>           print $ "SignumWord " ++ s ++ " = " ++ show (signum (read s::Word))
>   $
>
> I get the following response from jhc:
>
>   $ jhc Signum1.hs -o Signum1
>   jhc Signum1.hs -o Signum1
>   jhc 0.8.2 (mydniquipepo-32)
>   Finding Dependencies...
>   Using Ho Cache: '/home/tn/.jhc/cache'
>   Main                    [Signum1.hs]
>   Typechecking...
>   [1 of 1] Main             (.............................................)
>   Compiling...
>   [1 of 1] Main             <..................................................>
>   Collected Compilation...
>   -- TypeAnalyzeMethods
>   -- BoxifyProgram
>   -- Boxy WorkWrap
>   -- LambdaLift
>   Converting to Grin...
>   Updatable CAFS: 3
>   Constant CAFS:  6
>   Recursive CAFS: 0
>   WARNING: Wrapper still exists at grin transformation time: theMain$10::Jhc.Prim.Prim.(,) Jhc.Type.Word.Word::* Jhc.Prim.Prim.[] Jhc.Type.Basic.Char::*::*::* -> Jhc.Prim.Prim.[] Jhc.Type.Word.Word::*::*
>   WARNING: Wrapper still exists at grin transformation time: Jhc.Text.Read.119_isCharName::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   WARNING: Wrapper still exists at grin transformation time: Jhc.Text.Read.lexLitChar$10::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   WARNING: Wrapper still exists at grin transformation time: Jhc.Text.Read.lexLitChar$7::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   WARNING: Wrapper still exists at grin transformation time: Jhc.Text.Read.lexLitChar$4::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   WARNING: Wrapper still exists at grin transformation time: Jhc.Text.Read.78_isIdChar::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   WARNING: Wrapper still exists at grin transformation time: Jhc.Text.Read.77_isSym::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   WARNING: Wrapper still exists at grin transformation time: Prelude.CType.isOctDigit::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   WARNING: Wrapper still exists at grin transformation time: Prelude.CType.isDigit::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   WARNING: Wrapper still exists at grin transformation time: Prelude.CType.isHexDigit::Jhc.Type.Basic.Char::* -> Jhc.Prim.Prim.Bool::*
>   -- Speculative Execution Optimization
>   -- Node Usage Analysis
>   -- Grin Devolution
>   Writing "/tmp/jhc_nEVZY9/main_code.c"
>   Running: gcc /tmp/jhc_nEVZY9/rts/profile.c /tmp/jhc_nEVZY9/rts/rts_support.c /tmp/jhc_nEVZY9/rts/gc_none.c /tmp/jhc_nEVZY9/rts/jhc_rts.c /tmp/jhc_nEVZY9/lib/lib_cbits.c /tmp/jhc_nEVZY9/rts/gc_jgc.c /tmp/jhc_nEVZY9/rts/stableptr.c -I/tmp/jhc_nEVZY9/cbits -I/tmp/jhc_nEVZY9 /tmp/jhc_nEVZY9/main_code.c -o Signum1 '-std=gnu99' -D_GNU_SOURCE '-falign-functions=4' -ffast-math -Wextra -Wall -Wno-unused-parameter -fno-strict-aliasing -DNDEBUG -O3 '-D_JHC_GC=_JHC_GC_JGC'
>   In file included from /tmp/jhc_nEVZY9/jhc_rts_header.h:72:0,
>                    from /tmp/jhc_nEVZY9/main_code.c:5:
>   /tmp/jhc_nEVZY9/main_code.c: In function 'ftheMain':
>   /tmp/jhc_nEVZY9/rts/jhc_rts.h:54:24: warning: statement with no effect [-Wunused-value]
>    #define RAW_SET_16(w)  (wptr_t)(((uintptr_t)(w) << 16) | P_VALUE)
>                           ^
>   /tmp/jhc_nEVZY9/rts/jhc_rts.h:64:27: note: in expansion of macro 'RAW_SET_16'
>    #define SET_RAW_TAG(x)    RAW_SET_16(x)
>                              ^
>   /tmp/jhc_nEVZY9/main_code.c:5882:17: note: in expansion of macro 'SET_RAW_TAG'
>                    SET_RAW_TAG(CJhc_Prim_Prim_$LR);
>                    ^
>   /tmp/jhc_nEVZY9/main_code.c: In function 'ftheMain$d11':
>   /tmp/jhc_nEVZY9/main_code.c:5946:21: error: duplicate case value
>                        case 0:
>                        ^
>   /tmp/jhc_nEVZY9/main_code.c:5942:21: error: previously used here
>                        case 0:
>                        ^
>   Exiting abnormally. Work directory is '/tmp/jhc_nEVZY9'
>   jhc: user error (C code did not compile.)
>   $
>
> In /tmp/jhc_nEVZY9/main_code.c, I find:
>
>   ftheMain$d11(gc_t gc)
>   {
>           wptr_t v100008;
>           wptr_t v100012;
>           wptr_t v100016;
>           v100008 = fJhc_Text_Read_nonnull(gc,SET_RAW_TAG(P1__Prelude_CType_isDigit),c186);
>           sptr_t v94776804 = demote(v100008);
>           v100012 = ftheMain$d7(gc,v94776804);
>           v100016 = fJhc_Basics_concatMap(gc,SET_RAW_TAG(P1__theMain$d10),v100012);
>           if (SET_RAW_TAG(CJhc_Prim_Prim_$BE) == v100016) {
>               jhc_error("Prelude.error: Prelude.read: no parse");
>               return NULL;
>           } else {
>               sptr_t v1868;
>               sptr_t v1870;
>               /* ("CJhc.Prim.Prim.:" ni1868 ni1870) */
>               v1868 = ((struct sCJhc_Prim_Prim_$x3a*)v100016)->a1;
>               v1870 = ((struct sCJhc_Prim_Prim_$x3a*)v100016)->a2;
>               {   gc_frame0(gc,1,v1868);
>                   wptr_t v100018 = eval(gc,v1870);
>                   if (SET_RAW_TAG(CJhc_Prim_Prim_$BE) == v100018) {
>                       uint32_t v84995212;
>                       wptr_t v100020 = eval(gc,v1868);
>                       v84995212 = ((struct sCJhc_Type_Word_Word*)v100020)->a1;
>                       switch (v84995212) {
>                       case 0:
>                           {   return PROMOTE(c187);
>                           }
>                           break;
>                       case 0:
>                           {   return PROMOTE(c188);
>                           }
>                           break;
>                       default:
>                           {   return PROMOTE(c189);
>                           }
>                       break;
>                       }
>                   } else {
>                       /* ("CJhc.Prim.Prim.:" ni0 ni0) */
>                       jhc_error("Prelude.error: Prelude.read: ambiguous parse");
>                       return NULL;
>                   }
>               }
>           }
>   }
>
> I have checked the jhc mailing list back to January 2013, but could not
> find anything that seemed to address this, so any advice on how to
> proceed would be most appreciated.
>
> Additional information: I have built jhc from
>
>   http://repetae.net/dist/jhc-0.8.2.tar.gz
>
> The build (make jhc) failed initially with
>
>   ...
>   [ 71 of 186] Compiling Util.Gen         ( src/Util/Gen.hs, src/Util/Gen.o )
>
>   src/Util/Gen.hs:11:35:
>       Module `GenUtil' does not export `intercalate'
>   make[1]: *** [jhc] Error 1
>   make[1]: Leaving directory `/home/tn/tn/jhc/jhc-0.8.2'
>   make: *** [all] Error 2
>
> Removing ", intercalate" from the line
>
>   import GenUtil hiding(replicateM, intercalate)
>
> in jhc-0.8.2/src/Util/Gen.hs seemed to fix that problem, however.
>
> I also attempted to build jhc from the darcs repository as it appeared
> 2014-Dec-04, but got:
>
>   ...
>   [121 of 198] Compiling Deriving.Ord     ( src/Deriving/Ord.hs, obj/norm/Deriving/Ord.o )
>   [122 of 198] Compiling Deriving.Traverse ( src/Deriving/Traverse.hs, obj/norm/Deriving/Traverse.o )
>
>   src/Deriving/Traverse.hs:29:56: parse error on input `->'
>   make: *** [jhc] Error 1
>
> src/Deriving/Traverse.hs contains:
>
>   29: deriveFunctor der at Derive {..} mod d at D { vars = reverse -> ~(fv:_), .. } = do
>
> Thanks a lot in advance for any help and advice.
>
> Best regards
> Thorkil
> _______________________________________________
> jhc mailing list
> jhc at haskell.org
> http://www.haskell.org/mailman/listinfo/jhc



-- 
John Meacham - http://notanumber.net/


More information about the jhc mailing list