[nhc-bugs] nhc98-1.16: Segmentation fault and wrong Integer computation

Thorkil Naur naur at post11.tele.dk
Thu Dec 4 10:00:10 EST 2003


Hello nhc-bugs,

Using nhc98-1.16 to experiment with some number-theoretic
computations (c.f. H. W. Lenstra: "Factoring integers with elliptic
curves", Annals of Math., 126 (1987), 649-673), I ran into a
"Segmentation fault" and also examples of inconsistent Integer
computations. The result of executing the same program varies with
the size of the heap (the +RTS -H<size> option).

I have reduced the size of the original program and attached the
resulting t5.hs. Using the also attached t5.sh, the program is
compiled and executed three times with varying heap size and with
three different outcomes: Segmentation fault, wrong result, OK
result. The OK result is verified by also running t5.hs with hugs.
The output t5.out of

  sh t5.sh >t5.out 2>&1

is also attached.

To attempt to re-create this behaviour, place t5.hs and t5.sh in a
fresh directory, adjust NHC98 and HUGS in t5.sh to point to the
installed nhc98 compiler and hugs interpreter, and run

  sh t5.sh

The t5.hs program attempts to factor the square of the Mersenne prime
2^127-1, that happens in the line

  putStr ( "t5: " ++ show ( ec 2 ((2^127-1)^2) 50 1 ) ++ "\n" )

of t5.hs. Not a particular useful endeavor, but it suffices to
illustrate the problem. The "50" in this line limits the list of
primes that are used in the elliptic curve method. It may be
possible to reduce this number and get a shorter computation that
illustrates similar problems. I have attempted to use (2^127-1)
instead of ((2^127-1)^2), but failed to illustrate the problem.

The behaviour is apparently consistent, but erratic, depending on the
specified heap size. In the present case, for example, a heap size of
10000 bytes gets the segmentation fault.

The ghc98 that I use is compiled (currently "make basic" only) from
nhc98src-1.16.tar.gz on a Redhat 8.0 Linux.

I would be most grateful to receive some advice on how to proceed in
this matter.

Thanks a lot.

Regards Thorkil
-------------- next part --------------
-- t5.hs: nhc98 Segmentation fault
-- 2003-Dec-03 / TN

module Main where

main
  = do
      putStr "t5: 2003-Dec-03 23.28\n"
      putStr ( "t5: " ++ show ( ec 2 ((2^127-1)^2) 50 1 ) ++ "\n" )

data ECPoint
  = ECUndefined { ecd :: Integer }
  | ECZero
  | ECNonzero { ecx, ecy :: Integer }
  deriving ( Show, Eq )

ec a n l1 d = osA0 (\(xs,a)->(1,show a)) (ecadd a n) ECZero pone ecext n l1 d

ecadd a n p1@( ECUndefined { ecd = d } ) p2 = p1
ecadd a n p1 p2@( ECUndefined { ecd = d } ) = p2

ecadd a n ECZero p = p
ecadd a n p ECZero = p

ecadd a n p1@( ECNonzero { ecx = x1, ecy = y1 } ) p2@( ECNonzero { ecx = x2, ecy = y2 } )
  = let
      (a1,b1,g1) = chinrem n (x1 - x2)
    in
      if g1 == 1 then
        eclambda n ((y1 - y2)*b1) p1 p2
      else
        if g1 == n then
          let
            (a2,b2,g2) = chinrem n (y1 + y2)
          in
            if g2 == 1 then
              eclambda n ((3*x1*x1 + a)*b2) p1 p2
            else
              if g2 == n then
                ECZero
              else
                ECUndefined { ecd = g2 }
        else
          ECUndefined { ecd = g1 }

ecext (ECUndefined { ecd=d }) = d
ecext _ = 1

eclambda n lambda ( ECNonzero { ecx = x1, ecy = y1 } ) ( ECNonzero { ecx = x2, ecy = y2 } )
  = let
      x3 = mod (lambda*lambda - x1 - x2) n
    in
      ECNonzero { ecx = x3, ecy = mod (lambda*(x1 - x3) - y1) n }

pone = ECNonzero 2 3

dikke a b = b `mod` a /= 0

pp l = [ last (takeWhile (<= max l p) (iterate (*p) p)) |
         p<-2:3:5:dropWhile (<=1) [ i*30+j | i<-[0..], j<-filter (dikke 5) (filter (dikke 3) (filter (dikke 2) [0..29] ) ) ]
       ]

osA0 cont op pzero pone ext n l
  = split
      cont
      n
      ( \(x:xs,_)-> x>l )
      ( \(x:xs,a)->(xs,repeter op pzero x a) )
      (\(_,p)->ext p)
      ( pp l, pone )

chinrem n 0 = (signum n,0,abs n)
chinrem n m
  = let
      (q,r) = divMod n m
      (a,b,g) = chinrem m r
    in
      (b,a-b*q,g)

repeter op p0 0 p = p0
repeter op p0 k p
  = let
      kpd2 = repeter op p0 (div k 2) p
      kp2 = op kpd2 kpd2
    in
      if mod k 2 == 0 then
        kp2
      else
        op p kp2

maxx ended j (x:xs) = if j <= 0 || ended x then x else maxx ended (j-1) xs

split cont n ended next ext s0 d
  = if ended s0 then
      cont s0
    else
      let
        si = maxx ended d (iterate next s0)
        f = gcd n (ext si)
      in
        if f /= 1 then
          if d > 1 then
            split cont n ended next ext s0 (d `div` 2)
          else
            (f,take 50 (show si))
        else
          split cont n ended next ext si d

-------------- next part --------------
A non-text attachment was scrubbed...
Name: t5.sh
Type: application/x-sh
Size: 993 bytes
Desc: not available
Url : http://haskell.org/pipermail/nhc-bugs/attachments/20031204/5d667f41/t5.sh
-------------- next part --------------
t5.sh: Compile and run t5.hs to demonstrate nhc98 errors
t5.sh: NHC98="/home/tn/tn/install/nhc98-1.16/bin/nhc98"
t5.sh: HUGS="/usr/bin/hugs"
t5.sh: The /home/tn/tn/install/nhc98-1.16/bin/nhc98 version
/home/tn/tn/install/nhc98-1.16/bin/nhc98: v1.16 (2003-03-08)
  [ config: ix86-Linux/ by tn at localhost.localdomain on 26 Nov 2003 ]
t5.sh: Compile t5.hs
t5.sh: Execute t5 with heap 2750 expect segmentation fault
t5.sh: line 32:  9544 Segmentation fault      ./t5 +RTS -H$HEAP -RTS
t5.sh: Execute t5 with heap 2850 expect bad result
t5: 2003-Dec-03 23.28
t5: (1,"ECNonzero{ecx=10056118526409282227882113625406169321030314134537061289008231480722376351167320974760949454696077000460638009104751975093078356864233612608605123134717095633649184435611052285743401188397677859013856366538443238627713037970249046070229764333151555543706711933058199402566552830997211831839253950321094359,ecy=9212105258012566741306296285235372378677460900634096020691184526927905553403}")
t5.sh: Execute t5 with heap 100000 expect OK result
t5: 2003-Dec-03 23.28
t5: (1,"ECNonzero{ecx=1385648967195669950544729455662170485948476705396552044230404978515828326843,ecy=9212105258012566741306296285235372378677460900634096020691184526927905553403}")
t5.sh: Verify t5.hs using hugs
__   __ __  __  ____   ___      _________________________________________
||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell 98 standard
||___|| ||__|| ||__||  __||     Copyright (c) 1994-2002
||---||         ___||           World Wide Web: http://haskell.org/hugs
||   ||                         Report bugs to: hugs-bugs at haskell.org
||   || Version: November 2002  _________________________________________

Haskell 98 mode: Restart with command line option -98 to enable extensions

Reading file "/usr/lib/hugs/lib/Prelude.hs":
Parsing       Dependency analysis                   Type checking             Compiling         Reading file "t5.hs":
Parsing       Dependency analysis                   Type checking             Compiling         
Hugs session for:
/usr/lib/hugs/lib/Prelude.hs
t5.hs
Type :? for help
Main> t5: 2003-Dec-03 23.28
t5: (1,"ECNonzero{ecx=1385648967195669950544729455662170485948476705396552044230404978515828326843,ecy=9212105258012566741306296285235372378677460900634096020691184526927905553403}")

Main> [Leaving Hugs]
t5.sh: Ended


More information about the Nhc-bugs mailing list