Problems with "Hugs for Windows"

David Gray dgray@mailhost.compapp.dcu.ie
Wed, 10 Apr 2002 11:56:53 +0100


This is a multi-part message in MIME format.

------=_NextPart_000_0008_01C1E086.CE26BFD0
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: 7bit

I have students using Hugs for Windows, Version: December 2001.

Unfortunately, string handling appears to be somewhat erratic.

I have attached one example.

If this program is loaded and the following expression evaluated a number of
times, each evaluation gives a different (usually wrong) result.

dose (p,x) i

Everything works correctly with the command-line version of HUGS.

Thank you for your time.

David Gray

------=_NextPart_000_0008_01C1E086.CE26BFD0
Content-Type: Haskell Literate Program/octet-stream;
	name="code.lhs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="code.lhs"

>p =3D 5213619424271520371687014113170182341777563603680354416779
>x =3D 2365478234875800278
>


>i =3D   =
[(2388444081816277917038776738325937333223106223667114720968,260309583890=
0532828755390205322926331209103348008185108166),
>       =
(390933407333658619415739786262618313087510858735381122857,20904623112006=
87802040943886757409678442677610406699441905),
>       =
(2289303300340083412202151320082427988085327747764283838404,3112984294281=
640998021618999973614484142017072579079659634),
>       =
(1627101016633148526444375572709312560878470294452647198711,4098928924038=
241556099036036547032495809092526712121937007),
>       =
(4153059004927285334962430477267247428979278245406079131335,1072034811346=
234751995393587824702247060738122297710170512),
>       =
(1091579332383111336528553513019596493793816901113257129316,3039388519959=
517806090334164542246061331701118109938154994),
>       =
(4502131123589669239184104916614962340216632395860628541292,1628885955499=
604138164213360211450891152374944951261412804)]
>=20



>priv =3D =
1109213767215675653719813211280873862575690488108498658784708773697635810=
490325666729202742944087803

>str =3D ds_EG(p,x) i

>

>ds_EG :: (Integer,Integer) -> [(Integer,Integer)] -> String
>ds_EG (p,x) [] =3D error "Please include Cyphertext"
>ds_EG (p,x) i =3D intToString (combine (digits p) i2) where i2 =3D =
ds_EGstep1 (p,x) i []
>ds_EGstep1 (p,x) [] ints =3D ints=20
>ds_EGstep1 (p,x) (z:zs) ints =3D (((expm p (fst z) ((p - 1) - x)) * =
(snd z))`mod`p):ints
>                               ++ ds_EGstep1 (p,x) (zs) ints
=20


>expm :: Integer -> Integer -> Integer -> Integer
>expm m b k =3D                    -- b ^ k (mod m)
>   let
>     ex a k s
>        | k =3D=3D 0          =3D s
>        | k `mod` 2 =3D=3D 0  =3D ((ex $! (a*a `mod` m)) $! (k `div` =
2)) $!  s
>        | otherwise       =3D ((ex $! (a*a `mod` m)) $! (k `div` 2)) $! =
(s*a `mod` m)
>   in ex b k 1

>digits :: Integer -> Integer
>-- digits x =3D (len(split 1 x)-1)        -- corrected
>digits x
>        | x1 =3D=3D y =3D x1
>        | otherwise =3D (x1-1)
>        where x1 =3D (len(split 1 x)); y =3D (len(split 1 (x `div` 9)))

>split :: Integer -> Integer -> [Integer]
>split d 0 =3D [0]
>split d i =3D let
>              splt d i is=20
>                        | i <=3D 10^d =3D i:is
>                        | otherwise =3D splt d (i `div` 10^d) ((i `mod` =
10^d):is)
>              in
>                splt d i []


-------------------------------------------------------------------------=
---------

>combine :: Integer -> [Integer] -> Integer
>combine d [] =3D 0
>combine d x =3D (head x)*10^(d*((len x)-1)) + combine d (tail x)

>len x=20
>     | x =3D=3D [] =3D 0
>     | otherwise =3D 1 + (len (tail x))


-------------------------------------------------------------------------=
---------

>stringToInt :: String -> Integer
>stringToInt s
>     | s =3D=3D [] =3D 0
>     | otherwise =3D 256^(len s - 1) *toInteger(ord (head s)) + =
(stringToInt (tail s))


-------------------------------------------------------------------------=
---------

>convertb :: Integer -> Integer -> [Integer]
>convertb b 0 =3D[0]
>convertb b n =3D let
>                cnv 0 s =3D s                             =20
>                cnv n s =3D cnv (n `div` b) ((n `mod` b):s)
>              in
>                cnv n []


-------------------------------------------------------------------------=
---------

>intToString 0 =3D []              -- Correction
>intToString i =3D let
>           zz =3D convertb 256 i
>           i2s [] s =3D s=20
>           i2s zz s =3D (chr (toInt(head(zz)))):s ++ i2s (tail zz) s
>         in
>           i2s zz []



------=_NextPart_000_0008_01C1E086.CE26BFD0--