From davidbak@attbi.com Thu Apr 10 05:10:28 2003 From: davidbak@attbi.com (David Bakin) Date: Wed, 9 Apr 2003 21:10:28 -0700 Subject: [nhc-users] Problem installing nhc98 1.16 using bootstrap-from-C method Message-ID: <000c01c2ff17$1efe05d0$9477e40c@girlsprout> This is a multi-part message in MIME format. ------=_NextPart_000_0009_01C2FEDC.7232B060 Content-Type: text/plain; charset="Windows-1252" Content-Transfer-Encoding: quoted-printable I'm having trouble building nhc98 using bootstrap-from-C - the following = shows the error I'm getting. It is actually executing in hmake3.config = at the following line (the hmakerc add command) N:/nhc98-1.16/script/hmake-config = N:/nhc98-1.16/lib/ix86-CYGWIN_NT-5.1/hmakerc add = N:/nhc98-1.16/script/nhc98 davidbak@girlsprout /ndrive/nhc98-1.16/src/hmake $ make config sh N:/nhc98-1.16/targets/ix86-CYGWIN_NT-5.1/hmake3.config hmake-config: Starting new config file in N:/nhc98-1.16/lib/ix86-CYGWIN_NT-5.1/hmakerc I/O error: action : openFile ReadMode on file: /cygdrive/c/TEMP\hmakeconfig.tmp gave : ENOENT (No such file or directory) hmake-config: compiler not known: 'N:/nhc98-1.16/script/nhc98' make: *** [config] Error 2 As you can see it thinks hmakeconfig.tmp is not there - and in fact it = is not. Though it is a temporary file - I'm wondering if the problem is = in RunAndReadStdout.hs where it does a removeFile - and has the comment = "file will not be removed until readFile closes it". Actually I don't = have the slightest idea if that is the problem or not. Anyhow, any hints on how I can get past this? Thanks! -- Dave ------=_NextPart_000_0009_01C2FEDC.7232B060 Content-Type: text/html; charset="Windows-1252" Content-Transfer-Encoding: quoted-printable
I'm having trouble building nhc98 using = bootstrap-from-C - the=20 following shows the error I'm getting.  It is actually executing in = hmake3.config at the following line (the hmakerc add = command)
 
N:/nhc98-1.16/script/hmake-config=20 N:/nhc98-1.16/lib/ix86-CYGWIN_NT-5.1/hmakerc   add=20 N:/nhc98-1.16/script/nhc98
davidbak@girlsprout=20 /ndrive/nhc98-1.16/src/hmake
$ make config
sh=20 N:/nhc98-1.16/targets/ix86-CYGWIN_NT-5.1/hmake3.config
hmake-config: = Starting=20 new config file in
  = N:/nhc98-1.16/lib/ix86-CYGWIN_NT-5.1/hmakerc
I/O=20 error:
  action :  openFile ReadMode
  on = file: =20 /cygdrive/c/TEMP\hmakeconfig.tmp
  gave   :  = ENOENT (No=20 such file or directory)
hmake-config: compiler not known:
 =20 'N:/nhc98-1.16/script/nhc98'
make: *** [config] Error 2
 
As you can see it thinks hmakeconfig.tmp is not = there - and in=20 fact it is not.  Though it is a temporary file - I'm wondering if = the=20 problem is in RunAndReadStdout.hs where it does a removeFile - and has = the=20 comment "file will not be removed until readFile closes it".  = Actually I=20 don't have the slightest idea if that is the problem or = not.
 
Anyhow, any hints on how I can get past = this?
 
Thanks!  -- Dave
------=_NextPart_000_0009_01C2FEDC.7232B060-- From davidbak@attbi.com Thu Apr 10 05:13:01 2003 From: davidbak@attbi.com (David Bakin) Date: Wed, 9 Apr 2003 21:13:01 -0700 Subject: Fw: [nhc-users] Problem installing nhc98 1.16 using bootstrap-from-C method Message-ID: <000c01c2ff17$7a63d990$9477e40c@girlsprout> This is a multi-part message in MIME format. ------=_NextPart_000_0009_01C2FEDC.CDADE0E0 Content-Type: text/plain; charset="Windows-1252" Content-Transfer-Encoding: quoted-printable Sorry for the second message here - I should have said I just installed = cygwin yesterday and it is v1.3.22-1. Also, I'm running on XP Pro. = Thanks! -- Dave ----- Original Message -----=20 From: David Bakin=20 To: nhc-users@haskell.org=20 Sent: Wednesday, April 09, 2003 9:10 PM Subject: [nhc-users] Problem installing nhc98 1.16 using = bootstrap-from-C method I'm having trouble building nhc98 using bootstrap-from-C - the following = shows the error I'm getting. It is actually executing in hmake3.config = at the following line (the hmakerc add command) N:/nhc98-1.16/script/hmake-config = N:/nhc98-1.16/lib/ix86-CYGWIN_NT-5.1/hmakerc add = N:/nhc98-1.16/script/nhc98 davidbak@girlsprout /ndrive/nhc98-1.16/src/hmake $ make config sh N:/nhc98-1.16/targets/ix86-CYGWIN_NT-5.1/hmake3.config hmake-config: Starting new config file in N:/nhc98-1.16/lib/ix86-CYGWIN_NT-5.1/hmakerc I/O error: action : openFile ReadMode on file: /cygdrive/c/TEMP\hmakeconfig.tmp gave : ENOENT (No such file or directory) hmake-config: compiler not known: 'N:/nhc98-1.16/script/nhc98' make: *** [config] Error 2 As you can see it thinks hmakeconfig.tmp is not there - and in fact it = is not. Though it is a temporary file - I'm wondering if the problem is = in RunAndReadStdout.hs where it does a removeFile - and has the comment = "file will not be removed until readFile closes it". Actually I don't = have the slightest idea if that is the problem or not. Anyhow, any hints on how I can get past this? Thanks! -- Dave ------=_NextPart_000_0009_01C2FEDC.CDADE0E0 Content-Type: text/html; charset="Windows-1252" Content-Transfer-Encoding: quoted-printable
Sorry for the second message here - I should have = said I just=20 installed cygwin yesterday and it is v1.3.22-1.  Also, I'm running = on XP=20 Pro.  Thanks!  -- Dave
 
----- Original Message -----=20
From: David = Bakin
To: nhc-users@haskell.org
Sent: Wednesday, April 09, 2003 9:10 PM
Subject: [nhc-users] Problem installing nhc98 1.16 using=20 bootstrap-from-C method

I'm having trouble building nhc98 using = bootstrap-from-C - the=20 following shows the error I'm getting.  It is actually executing in = hmake3.config at the following line (the hmakerc add = command)
 
N:/nhc98-1.16/script/hmake-config=20 N:/nhc98-1.16/lib/ix86-CYGWIN_NT-5.1/hmakerc   add=20 N:/nhc98-1.16/script/nhc98
davidbak@girlsprout=20 /ndrive/nhc98-1.16/src/hmake
$ make config
sh=20 N:/nhc98-1.16/targets/ix86-CYGWIN_NT-5.1/hmake3.config
hmake-config: = Starting=20 new config file in
  = N:/nhc98-1.16/lib/ix86-CYGWIN_NT-5.1/hmakerc
I/O=20 error:
  action :  openFile ReadMode
  on = file: =20 /cygdrive/c/TEMP\hmakeconfig.tmp
  gave   :  = ENOENT (No=20 such file or directory)
hmake-config: compiler not known:
 =20 'N:/nhc98-1.16/script/nhc98'
make: *** [config] Error 2
 
As you can see it thinks hmakeconfig.tmp is not = there - and in=20 fact it is not.  Though it is a temporary file - I'm wondering if = the=20 problem is in RunAndReadStdout.hs where it does a removeFile - and has = the=20 comment "file will not be removed until readFile closes it".  = Actually I=20 don't have the slightest idea if that is the problem or = not.
 
Anyhow, any hints on how I can get past = this?
 
Thanks!  -- Dave
------=_NextPart_000_0009_01C2FEDC.CDADE0E0-- From Malcolm.Wallace@cs.york.ac.uk Thu Apr 10 10:03:29 2003 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Thu, 10 Apr 2003 10:03:29 +0100 Subject: [nhc-users] Problem installing nhc98 1.16 using bootstrap-from-C method In-Reply-To: <000c01c2ff17$7a63d990$9477e40c@girlsprout> References: <000c01c2ff17$7a63d990$9477e40c@girlsprout> Message-ID: <20030410100329.3223d433.Malcolm.Wallace@cs.york.ac.uk> "David Bakin" writes: > I'm having trouble building nhc98 using bootstrap-from-C - the following > shows the error I'm getting. It is actually executing in hmake3.config > > I/O error: > action : openFile ReadMode > on file: /cygdrive/c/TEMP\hmakeconfig.tmp > gave : ENOENT (No such file or directory) I believe the problem here is the mixture of directory separators. When compiled by ghc the mix doesn't matter, but it does matter in a pure C-under-cygwin build, which likes to pretend to be Unix as much as possible. In src/hmake/RunAndReadStdout.hs, try changing tmpfile root = ... if windows then (tmp++"\\"++root++".tmp") to then (tmp++"/"++root++".tmp") Then, because you are bootstrapping via C, you will need to re-generate the .hc file from this source before continuing with the build: ( cd src/hmake && ../../script/nhc98 -C RunAndReadStdout.hs ) make Regards, Malcolm From Malcolm.Wallace@cs.york.ac.uk Thu Apr 10 14:58:12 2003 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Thu, 10 Apr 2003 14:58:12 +0100 Subject: [nhc-users] porting to MS VC++.NET In-Reply-To: <000a01c2ff62$a047e7a0$9477e40c@girlsprout> References: <000c01c2ff17$7a63d990$9477e40c@girlsprout> <20030410100329.3223d433.Malcolm.Wallace@cs.york.ac.uk> <000a01c2ff62$a047e7a0$9477e40c@girlsprout> Message-ID: <20030410145812.287a8998.Malcolm.Wallace@cs.york.ac.uk> "David Bakin" writes: > By the way, I'd like to try to port nhc98 to Microsoft VC++.NET - just to > provide a more convenient environment. I am just getting started with nhc > (as you see) and have no idea how big a project this would be, though I can > imagine some of the common areas of difficulty (e.g., annoying things like > the file separators below). Has anyone tried this? I don't think anyone has tried it before. Aside from the basic platform differences you can already guess: * Add .exe to executable filenames * Use \ as a directory separator instead of / * PATH uses ; instead of : the main obstacles will be: * The Makefiles assume some GNU extensions * The Top-level drivers are shell-scripts On the latter point, nhc98 (and hmake) have shell-script drivers to interpret arguments and call the various stages (pre-processor, Haskell compiler, C compiler, assembler, linker, etc.). Since native windows doesn't have the Bourne shell, you either need to haul in Cygwin's 'bash' (and associated tools like sed, cut, etc) just for that job, or re-code the scripts (perhaps in Haskell?). Regards, Malcolm From davidbak@attbi.com Thu Apr 10 18:05:25 2003 From: davidbak@attbi.com (David Bakin) Date: Thu, 10 Apr 2003 10:05:25 -0700 Subject: [nhc-users] Problem installing nhc98 1.16 using bootstrap-from-C method References: <000c01c2ff17$7a63d990$9477e40c@girlsprout> <20030410100329.3223d433.Malcolm.Wallace@cs.york.ac.uk> Message-ID: <001701c2ff83$6163bc00$9477e40c@girlsprout> Got it working with that fix - although I couldn't get the nhc98 -C step to work to compile the fixed .hs file (it complained about not finding Platform.hi in any of several locations, even after a full successful build there is still no Platform.hi anywhere - should there be?) so I just hand-modified the (encoded) string constant in RunAndReadStdout.hc.) So now I'm free to play with nhc98, thanks! I have another question though: on the "Building/Installing nhc98" page it says that if you build using the C compiler only the resulting compiler is slower. Why? I would have thought the hc files were directly from nhc (or ghc?) in the first place (and if from ghc then wouldn't the resulting compiler be faster than an nhc-bootstrapped compiler)? Anyway, now that I have built from C sources should I bootstrap through the resulting nhc98? Plus a small correction for the "Installing nhc98 under Windows" page: you also need cygwin's 'bc' tool which is not installed by default. -- Dave ----- Original Message ----- From: "Malcolm Wallace" To: "David Bakin" Cc: Sent: Thursday, April 10, 2003 2:03 AM Subject: Re: [nhc-users] Problem installing nhc98 1.16 using bootstrap-from-C method > "David Bakin" writes: > > > I'm having trouble building nhc98 using bootstrap-from-C - the following > > shows the error I'm getting. It is actually executing in hmake3.config > > > > I/O error: > > action : openFile ReadMode > > on file: /cygdrive/c/TEMP\hmakeconfig.tmp > > gave : ENOENT (No such file or directory) > > I believe the problem here is the mixture of directory separators. > When compiled by ghc the mix doesn't matter, but it does matter in a > pure C-under-cygwin build, which likes to pretend to be Unix as much > as possible. > > In src/hmake/RunAndReadStdout.hs, try changing > > tmpfile root = > ... > if windows > then (tmp++"\\"++root++".tmp") > to > then (tmp++"/"++root++".tmp") > > Then, because you are bootstrapping via C, you will need to re-generate > the .hc file from this source before continuing with the build: > > ( cd src/hmake && ../../script/nhc98 -C RunAndReadStdout.hs ) > make > > Regards, > Malcolm From Malcolm.Wallace@cs.york.ac.uk Thu Apr 10 18:40:17 2003 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Thu, 10 Apr 2003 18:40:17 +0100 Subject: [nhc-users] Problem installing nhc98 1.16 using bootstrap-from-C method In-Reply-To: <001701c2ff83$6163bc00$9477e40c@girlsprout> References: <000c01c2ff17$7a63d990$9477e40c@girlsprout> <20030410100329.3223d433.Malcolm.Wallace@cs.york.ac.uk> <001701c2ff83$6163bc00$9477e40c@girlsprout> Message-ID: <20030410184017.30829f81.Malcolm.Wallace@cs.york.ac.uk> "David Bakin" writes: > Got it working with that fix - although I couldn't get the nhc98 -C step to > work to compile the fixed .hs file (it complained about not finding > Platform.hi in any of several locations, even after a full successful build > there is still no Platform.hi anywhere - should there be?) I now see that RunAndReadStdout imports Platform, so you would have needed to nhc98-compile the latter to generate a .hi file before you could successfully nhc98-compile the former. The .hi files are not needed when bootstrapping via C, but of course the Haskell compiler itself requires them (and generates them). > I have another question though: on the "Building/Installing nhc98" page it > says that if you build using the C compiler only the resulting compiler is > slower. Why? The C-bootstrapped compiler is exactly the nhc98 compiler built with itself. Any program built by nhc98 runs on average 4-5x slower than the same program built by ghc - this is the usual tradeoff between space and speed optimisations. > Anyway, now that I have built from C sources should I bootstrap > through the resulting nhc98? I wouldn't recommend it. You will end up with an identical compiler, but spend a lot of time getting there! > Plus a small correction for the "Installing nhc98 under Windows" page: you > also need cygwin's 'bc' tool which is not installed by default. I don't recall using 'bc' anywhere in the build scripts - can you let me know the location where you needed it please? Regards, Malcolm From davidbak@attbi.com Thu Apr 10 18:48:48 2003 From: davidbak@attbi.com (David Bakin) Date: Thu, 10 Apr 2003 10:48:48 -0700 Subject: [nhc-users] Problem installing nhc98 1.16 using bootstrap-from-C method References: <000c01c2ff17$7a63d990$9477e40c@girlsprout><20030410100329.3223d433.Malcolm.Wallace@cs.york.ac.uk><001701c2ff83$6163bc00$9477e40c@girlsprout> <20030410184017.30829f81.Malcolm.Wallace@cs.york.ac.uk> Message-ID: <003f01c2ff89$714fe8e0$9477e40c@girlsprout> script/tprofprel line 21 ----- Original Message ----- From: "Malcolm Wallace" To: "David Bakin" Cc: Sent: Thursday, April 10, 2003 10:40 AM Subject: Re: [nhc-users] Problem installing nhc98 1.16 using bootstrap-from-C method > > > Plus a small correction for the "Installing nhc98 under Windows" page: you > > also need cygwin's 'bc' tool which is not installed by default. > > I don't recall using 'bc' anywhere in the build scripts - can you > let me know the location where you needed it please? From dominic.steinitz@blueyonder.co.uk Mon Apr 28 20:41:19 2003 From: dominic.steinitz@blueyonder.co.uk (Dominic Steinitz) Date: Mon, 28 Apr 2003 20:41:19 +0100 Subject: [nhc-users] Crytpo for nhc Message-ID: <000a01c30dbe$249b2300$1464a8c0@canterburysoftware.com> This is a multi-part message in MIME format. ------=_NextPart_000_0007_01C30DC6.85F1AE00 Content-Type: text/plain; charset="iso-8859-1" Content-Transfer-Encoding: 7bit I have been trying to write a Crypto library and so far it works with ghc and hugs. Am I right in thinking I am going to struggle with nhc? It uses Word8 and Word64 heavily. For example, cipher block chaining relies on xoring Word64. I attach the library and a test program. I'd be grateful for any suggestions on how to make it work with nhc. Dominic Steinitz ------=_NextPart_000_0007_01C30DC6.85F1AE00 Content-Type: application/octet-stream; name="Crypto.hs" Content-Transfer-Encoding: quoted-printable Content-Disposition: attachment; filename="Crypto.hs" -------------------------------------------------------------------------= ----=0A= -- |=0A= -- Module : Data.Crypto=0A= -- Copyright : (c) Ian Lynagh, Dominic Steinitz 2001-2003=0A= -- License : BSD-style (see the file libraries/base/LICENSE)=0A= -- =0A= -- Maintainer : dominic.steinitz@blueyonder.co.uk=0A= -- Stability : experimental=0A= -- Portability : non-portable=0A= --=0A= -- Cryptographic library based on contributions from Ian Lynagh=0A= -- .=0A= --=0A= -- Requires Bits, Word, Word64 and multi-parameter type classes.=0A= --=0A= -- This library currently supports DES Electronic Codebook Mode (ECB) = mode=0A= -- and Cipher Block Chainig (CBC) mode.=0A= -- =0A= -------------------------------------------------------------------------= ----=0A= =0A= module Crypto (=0A= -- * Types=0A= Octet,=0A= -- * Function types=0A= des, unDes,=0A= cbc, unCbc, =0A= pkcs5, unPkcs5,=0A= toOctets, fromOctets=0A= -- * Example Usage=0A= -- $usage=0A= ) where=0A= =0A= import Data.Word=0A= import Data.Bits=0A= import List=0A= =0A= {- BEGIN_HUGS_ONLY -}=0A= =0A= import ZordHUGS=0A= =0A= {- END_HUGS_ONLY -}=0A= =0A= {- BEGIN_GHC_ONLY=0A= =0A= type Zord64 =3D Word64=0A= =0A= END_GHC_ONLY -}=0A= =0A= {- $usage=0A= =0A= @=0A= module Main(main) where=0A= @=0A= =0A= @=0A= import Crypto=0A= @=0A= =0A= @=0A= import Char=0A= @=0A= =0A= @=0A= plainText =3D "Good morning Mr. Phelps. Your m" ++=0A= "ission,\nshould you choose to acc" ++=0A= "ept it, is to learn to use DES.\NUL"=0A= @=0A= =0A= @=0A= iv =3D 0x0123456789abcdef=0A= @=0A= =0A= @=0A= key =3D 0x42652d4861707079=0A= @=0A= =0A= @=0A= cipherText =3D cbc des iv key $ pkcs5 $ map (fromIntegral . ord) = plainText=0A= @=0A= =0A= @=0A= plainText' =3D map (chr . fromIntegral) $ unPkcs5 $ unCbc unDes iv key = cipherText=0A= @=0A= =0A= @=0A= main =3D putStrLn plainText'=0A= @=0A= =0A= -}=0A= =0A= type Rotation =3D Int=0A= type Key =3D Zord64=0A= type Message =3D Zord64=0A= type Enc =3D Zord64=0A= type InitVector =3D Zord64=0A= =0A= type BitsX =3D [Bool]=0A= type Bits4 =3D [Bool]=0A= type Bits6 =3D [Bool]=0A= type Bits32 =3D [Bool]=0A= type Bits48 =3D [Bool]=0A= type Bits56 =3D [Bool]=0A= type Bits64 =3D [Bool]=0A= =0A= instance Num [Bool]=0A= =0A= instance Bits [Bool] where=0A= a `xor` b =3D (zipWith (\x y -> (not x && y) || (x && not y)) a b)=0A= rotate bits rot =3D drop rot' bits ++ take rot' bits=0A= where rot' =3D rot `mod` (length bits)=0A= =0A= bitify :: Zord64 -> Bits64=0A= bitify w =3D map (\b -> w .&. (shiftL 1 b) /=3D 0) [63,62..0]=0A= =0A= unbitify :: Bits64 -> Zord64=0A= unbitify bs =3D foldl (\i b -> if b then 1 + shiftL i 1 else shiftL i 1) = 0 bs=0A= =0A= initial_permutation :: Bits64 -> Bits64=0A= initial_permutation mb =3D map ((!!) mb) i=0A= where i =3D [57, 49, 41, 33, 25, 17, 9, 1, 59, 51, 43, 35, 27, 19, = 11, 3,=0A= 61, 53, 45, 37, 29, 21, 13, 5, 63, 55, 47, 39, 31, 23, 15, = 7,=0A= 56, 48, 40, 32, 24, 16, 8, 0, 58, 50, 42, 34, 26, 18, 10, = 2,=0A= 60, 52, 44, 36, 28, 20, 12, 4, 62, 54, 46, 38, 30, 22, 14, = 6]=0A= =0A= key_transformation :: Bits64 -> Bits56=0A= key_transformation kb =3D map ((!!) kb) i=0A= where i =3D [56, 48, 40, 32, 24, 16, 8, 0, 57, 49, 41, 33, 25, 17,=0A= 9, 1, 58, 50, 42, 34, 26, 18, 10, 2, 59, 51, 43, 35,=0A= 62, 54, 46, 38, 30, 22, 14, 6, 61, 53, 45, 37, 29, 21,=0A= 13, 5, 60, 52, 44, 36, 28, 20, 12, 4, 27, 19, 11, 3]=0A= =0A= des_enc :: Message -> Key -> Enc=0A= des_enc =3D do_des [1,2,4,6,8,10,12,14,15,17,19,21,23,25,27,28]=0A= =0A= des_dec :: Message -> Key -> Enc=0A= des_dec =3D do_des [28,27,25,23,21,19,17,15,14,12,10,8,6,4,2,1]=0A= =0A= do_des :: [Rotation] -> Message -> Key -> Enc=0A= do_des rots m k =3D des_work rots (takeDrop 32 mb) kb=0A= where kb =3D key_transformation $ bitify k=0A= mb =3D initial_permutation $ bitify m=0A= =0A= des_work :: [Rotation] -> (Bits32, Bits32) -> Bits56 -> Enc=0A= des_work [] (ml, mr) _ =3D unbitify $ final_perm $ (mr ++ ml)=0A= des_work (r:rs) mb kb =3D des_work rs mb' kb=0A= where mb' =3D do_round r mb kb=0A= =0A= do_round :: Rotation -> (Bits32, Bits32) -> Bits56 -> (Bits32, Bits32)=0A= do_round r (ml, mr) kb =3D (mr, m')=0A= where kb' =3D get_key kb r=0A= comp_kb =3D compression_permutation kb'=0A= expa_mr =3D expansion_permutation mr=0A= res =3D comp_kb `xor` expa_mr=0A= res' =3D tail $ iterate (trans 6) ([], res)=0A= trans n (_, b) =3D (take n b, drop n b)=0A= res_s =3D concat $ zipWith (\f (x,_) -> f x) [s_box_1, s_box_2,=0A= s_box_3, s_box_4,=0A= s_box_5, s_box_6,=0A= s_box_7, s_box_8] res'=0A= res_p =3D p_box res_s=0A= m' =3D res_p `xor` ml=0A= =0A= get_key :: Bits56 -> Rotation -> Bits56=0A= get_key kb r =3D kb'=0A= where (kl, kr) =3D takeDrop 28 kb=0A= kb' =3D rotateL kl r ++ rotateL kr r=0A= =0A= compression_permutation :: Bits56 -> Bits48=0A= compression_permutation kb =3D map ((!!) kb) i=0A= where i =3D [13, 16, 10, 23, 0, 4, 2, 27, 14, 5, 20, 9,=0A= 22, 18, 11, 3, 25, 7, 15, 6, 26, 19, 12, 1,=0A= 40, 51, 30, 36, 46, 54, 29, 39, 50, 44, 32, 47,=0A= 43, 48, 38, 55, 33, 52, 45, 41, 49, 35, 28, 31]=0A= =0A= expansion_permutation :: Bits32 -> Bits48=0A= expansion_permutation mb =3D map ((!!) mb) i=0A= where i =3D [31, 0, 1, 2, 3, 4, 3, 4, 5, 6, 7, 8,=0A= 7, 8, 9, 10, 11, 12, 11, 12, 13, 14, 15, 16,=0A= 15, 16, 17, 18, 19, 20, 19, 20, 21, 22, 23, 24,=0A= 23, 24, 25, 26, 27, 28, 27, 28, 29, 30, 31, 0]=0A= =0A= s_box :: [[Word8]] -> Bits6 -> Bits4=0A= s_box s [a,b,c,d,e,f] =3D to_bool 4 $ (s !! row) !! col=0A= where row =3D sum $ zipWith numericise [a,f] [1, 0]=0A= col =3D sum $ zipWith numericise [b,c,d,e] [3, 2, 1, 0]=0A= numericise =3D (\x y -> if x then 2^y else 0)=0A= to_bool 0 _ =3D []=0A= to_bool n i =3D ((i .&. 8) =3D=3D 8):to_bool (n-1) (shiftL i 1)=0A= =0A= s_box_1 :: Bits6 -> Bits4=0A= s_box_1 =3D s_box i=0A= where i =3D [[14, 4, 13, 1, 2, 15, 11, 8, 3, 10, 6, 12, 5, 9, = 0, 7],=0A= [ 0, 15, 7, 4, 14, 2, 13, 1, 10, 6, 12, 11, 9, 5, 3, = 8],=0A= [ 4, 1, 14, 8, 13, 6, 2, 11, 15, 12, 9, 7, 3, 10, 5, = 0],=0A= [15, 12, 8, 2, 4, 9, 1, 7, 5, 11, 3, 14, 10, 0, 6, = 13]]=0A= =0A= s_box_2 :: Bits6 -> Bits4=0A= s_box_2 =3D s_box i=0A= where i =3D [[15, 1, 8, 14, 6, 11, 3, 4, 9, 7, 2, 13, 12, 0, = 5, 10],=0A= [3, 13, 4, 7, 15, 2, 8, 14, 12, 0, 1, 10, 6, 9, = 11, 5],=0A= [0, 14, 7, 11, 10, 4, 13, 1, 5, 8, 12, 6, 9, 3, 2, = 15],=0A= [13, 8, 10, 1, 3, 15, 4, 2, 11, 6, 7, 12, 0, 5, = 14, 9]]=0A= =0A= s_box_3 :: Bits6 -> Bits4=0A= s_box_3 =3D s_box i=0A= where i =3D [[10, 0, 9, 14 , 6, 3, 15, 5, 1, 13, 12, 7, 11, 4, = 2, 8],=0A= [13, 7, 0, 9, 3, 4, 6, 10, 2, 8, 5, 14, 12, 11, 15, = 1],=0A= [13, 6, 4, 9, 8, 15, 3, 0, 11, 1, 2, 12, 5, 10, 14, = 7],=0A= [1, 10, 13, 0, 6, 9, 8, 7, 4, 15, 14, 3, 11, 5, 2, = 12]]=0A= =0A= s_box_4 :: Bits6 -> Bits4=0A= s_box_4 =3D s_box i=0A= where i =3D [[7, 13, 14, 3, 0, 6, 9, 10, 1, 2, 8, 5, 11, 12, = 4, 15],=0A= [13, 8, 11, 5, 6, 15, 0, 3, 4, 7, 2, 12, 1, 10, 14, = 9],=0A= [10, 6, 9, 0, 12, 11, 7, 13, 15, 1, 3, 14, 5, 2, 8, = 4],=0A= [3, 15, 0, 6, 10, 1, 13, 8, 9, 4, 5, 11, 12, 7, 2, = 14]]=0A= =0A= s_box_5 :: Bits6 -> Bits4=0A= s_box_5 =3D s_box i=0A= where i =3D [[2, 12, 4, 1, 7, 10, 11, 6, 8, 5, 3, 15, 13, 0, = 14, 9],=0A= [14, 11, 2, 12, 4, 7, 13, 1, 5, 0, 15, 10, 3, 9, 8, = 6],=0A= [4, 2, 1, 11, 10, 13, 7, 8, 15, 9, 12, 5, 6, 3, 0, = 14],=0A= [11, 8, 12, 7, 1, 14, 2, 13, 6, 15, 0, 9, 10, 4, 5, = 3]]=0A= =0A= s_box_6 :: Bits6 -> Bits4=0A= s_box_6 =3D s_box i=0A= where i =3D [[12, 1, 10, 15, 9, 2, 6, 8, 0, 13, 3, 4, 14, 7, = 5, 11],=0A= [10, 15, 4, 2, 7, 12, 9, 5, 6, 1, 13, 14, 0, 11, 3, = 8],=0A= [9, 14, 15, 5, 2, 8, 12, 3, 7, 0, 4, 10, 1, 13, 11, = 6],=0A= [4, 3, 2, 12, 9, 5, 15, 10, 11, 14, 1, 7, 6, 0, 8, = 13]]=0A= =0A= s_box_7 :: Bits6 -> Bits4=0A= s_box_7 =3D s_box i=0A= where i =3D [[4, 11, 2, 14, 15, 0, 8, 13, 3, 12, 9, 7, 5, 10, = 6, 1],=0A= [13, 0, 11, 7, 4, 9, 1, 10, 14, 3, 5, 12, 2, 15, 8, = 6],=0A= [1, 4, 11, 13, 12, 3, 7, 14, 10, 15, 6, 8, 0, 5, 9, = 2],=0A= [6, 11, 13, 8, 1, 4, 10, 7, 9, 5, 0, 15, 14, 2, 3, = 12]]=0A= =0A= s_box_8 :: Bits6 -> Bits4=0A= s_box_8 =3D s_box i=0A= where i =3D [[13, 2, 8, 4, 6, 15, 11, 1, 10, 9, 3, 14, 5, 0, = 12, 7],=0A= [1, 15, 13, 8, 10, 3, 7, 4, 12, 5, 6, 11, 0, 14, 9, = 2],=0A= [7, 11, 4, 1, 9, 12, 14, 2, 0, 6, 10, 13, 15, 3, 5, = 8],=0A= [2, 1, 14, 7, 4, 10, 8, 13, 15, 12, 9, 0, 3, 5, 6, = 11]]=0A= =0A= p_box :: Bits32 -> Bits32=0A= p_box kb =3D map ((!!) kb) i=0A= where i =3D [15, 6, 19, 20, 28, 11, 27, 16, 0, 14, 22, 25, 4, 17, 30, = 9,=0A= 1, 7, 23, 13, 31, 26, 2, 8, 18, 12, 29, 5, 21, 10, 3, = 24]=0A= =0A= final_perm :: Bits64 -> Bits64=0A= final_perm kb =3D map ((!!) kb) i=0A= where i =3D [39, 7, 47, 15, 55, 23, 63, 31, 38, 6, 46, 14, 54, 22, 62, = 30,=0A= 37, 5, 45, 13, 53, 21, 61, 29, 36, 4, 44, 12, 52, 20, 60, 28,=0A= 35, 3, 43, 11, 51, 19, 59, 27, 34, 2, 42, 10, 50, 18, 58, 26,=0A= 33, 1, 41, 9, 49, 17, 57, 25, 32, 0, 40 , 8, 48, 16, 56, 24]=0A= =0A= takeDrop :: Int -> [a] -> ([a], [a])=0A= takeDrop _ [] =3D ([], [])=0A= takeDrop 0 xs =3D ([], xs)=0A= takeDrop n (x:xs) =3D (x:ys, zs)=0A= where (ys, zs) =3D takeDrop (n-1) xs=0A= =0A= powersOf n =3D 1 : (map (*n) (powersOf n))=0A= =0A= toBase x =3D =0A= map fromIntegral .=0A= reverse .=0A= map (flip mod x) .=0A= takeWhile (/=3D0) .=0A= iterate (flip div x)=0A= =0A= -- * CBC or Cipher Block Chaining Mode=0A= =0A= -- | In CBC or Cipher Block Chaining mode each block is XORed with =0A= -- the previous enciphered block before encryption. For the first =0A= -- block we start with an initialization vector.=0A= =0A= cbc :: Bits block =3D>=0A= (key -> block -> block) -> =0A= block -> =0A= key ->=0A= [block] -> =0A= [block]=0A= =0A= cbc e iv k ps =3D =0A= ciphers where=0A= ciphers =3D map (e k) feedIns=0A= feedIns =3D zipWith xor (iv : ciphers) ps=0A= =0A= -- | To decipher in CBC or Cipher Block Chaining mode we decipher =0A= -- each block, then XOR the result with the previous block of =0A= -- plaintext result. Note that we treat the initialization vector as = the zeroth block of plaintext.=0A= =0A= unCbc :: Bits block =3D>=0A= (key -> block -> block) -> =0A= block -> =0A= key ->=0A= [block] -> =0A= [block]=0A= =0A= unCbc d iv k ms =3D=0A= outOfCbcs where=0A= beforeXOrs =3D map (d k) ms=0A= outOfCbcs =3D zipWith xor (iv : ms) beforeXOrs=0A= =0A= -- * PKCS#5 Padding Method=0A= =0A= -- | When the last block of plaintext is shorter than the block size = then it=0A= -- must be padded. PKCS#5 specifies that the padding octets should each =0A= -- contain the number of octets which must be stripped off. So, for = example,=0A= -- with a block size of 8, "0a0b0c" will be padded with "05" resulting in=0A= -- "0a0b0c0505050505". If the final block is a full block of 8 octets=0A= -- then a whole block of "0808080808080808" is appended.=0A= =0A= pkcs5 s =3D=0A= blocks where=0A= octetSize =3D (bitSize $ head blocks) `div` 8=0A= blocks =3D map fromOctets (unfoldr h $ concat $ unfoldr g s) =0A= g :: [Octet] -> Maybe ([Octet],[Octet])=0A= g x =0A= | l =3D=3D 0 =3D Nothing=0A= | l < octetSize =3D Just (t ++ (p (octetSize-l)), [])=0A= | d =3D=3D [] =3D Just (t ++ (p octetSize), [])=0A= | otherwise =3D Just (t, d)=0A= where l =3D length t=0A= t =3D take octetSize x=0A= d =3D drop octetSize x=0A= p n =3D replicate n (fromIntegral n)=0A= h :: [Octet] -> Maybe ([Octet],[Octet])=0A= h x =0A= | x =3D=3D [] =3D Nothing=0A= | otherwise =3D Just (take octetSize x, drop octetSize x)=0A= =0A= toOctets :: Integral a =3D> a -> [Octet]=0A= toOctets x =3D (toBase 256 . fromIntegral) x=0A= =0A= type Octet =3D Word8=0A= =0A= fromOctets :: Num a =3D> [Octet] -> a=0A= fromOctets x =3D =0A= sum $ zipWith (*) (powersOf 256) =0A= (reverse (map fromIntegral x))=0A= =0A= unPkcs5 ws =3D =0A= concat $ map toOctets (concat $ unfoldr g ws) where=0A= g :: (Integral a, Bits a) =3D> [a] -> Maybe ([a],[a])=0A= g x =0A= | t =3D=3D [] =3D Nothing=0A= | d =3D=3D [] =3D Just ([s], [])=0A= | otherwise =3D Just (t, d)=0A= where t =3D take 1 x=0A= d =3D drop 1 x=0A= u =3D head t=0A= octetSize =3D (bitSize u) `div` 8=0A= h x =3D take (octetSize - (fromIntegral (last x))) x=0A= s =3D fromOctets $ h $ toOctets u=0A= =0A= -- * Basic DES Encryption=0A= =0A= -- | Basic DES encryption which takes a key and a block of plaintext =0A= -- and returns the encrypted block of ciphertext according to the = standard.=0A= =0A= des :: Zord64 -> Zord64 -> Zord64=0A= des =3D flip des_enc=0A= =0A= -- | Basic DES decryption which takes a key and a block of ciphertext and=0A= -- returns the decrypted block of plaintext according to the standard.=0A= =0A= unDes :: Zord64 -> Zord64 -> Zord64=0A= unDes =3D flip des_dec=0A= ------=_NextPart_000_0007_01C30DC6.85F1AE00 Content-Type: application/octet-stream; name="ITest.hs" Content-Transfer-Encoding: quoted-printable Content-Disposition: attachment; filename="ITest.hs" module Main(main) where=0A= =0A= import Crypto=0A= import Char=0A= =0A= plainText =3D "Good morning Mr. Phelps. Your m" ++=0A= "ission,\nshould you choose to acc" ++=0A= "ept it, is to learn to use DES.\NUL"=0A= =0A= iv =3D 0x0123456789abcdef=0A= =0A= key =3D 0x42652d4861707079=0A= =0A= cipherText =3D cbc des iv key $ pkcs5 $ map (fromIntegral . ord) = plainText=0A= =0A= plainText' =3D map (chr . fromIntegral) $ unPkcs5 $ unCbc unDes iv key = cipherText=0A= =0A= main =3D putStrLn plainText'=0A= ------=_NextPart_000_0007_01C30DC6.85F1AE00 Content-Type: application/octet-stream; name="ZordHUGS.lhs" Content-Transfer-Encoding: quoted-printable Content-Disposition: attachment; filename="ZordHUGS.lhs" =0A= > module ZordHUGS (Zord64) where=0A= =0A= > import Data.Word=0A= > import Data.Bits=0A= > import Numeric=0A= =0A= > data Zord64 =3D W64 {lo,hi::Word32} deriving (Eq, Ord, Bounded)=0A= =0A= > w64ToInteger W64{lo=3Dlo,hi=3Dhi} =3D toInteger lo + 0x100000000 * = toInteger hi=0A= > integerToW64 x =3D case x `quotRem` 0x100000000 of=0A= > (h,l) -> W64{lo=3DfromInteger l, hi=3DfromInteger h}=0A= =0A= > instance Show Zord64 where=0A= > showsPrec p =3D showInt . w64ToInteger=0A= =0A= > instance Read Zord64 where=0A= > readsPrec p s =3D [ (integerToW64 x,r) | (x,r) <- readDec s ]=0A= =0A= > instance Num Zord64 where=0A= > W64{lo=3Dlo_a,hi=3Dhi_a} + W64{lo=3Dlo_b,hi=3Dhi_b} =3D W64{lo=3Dlo', = hi=3Dhi'}=0A= > where lo' =3D lo_a + lo_b=0A= > hi' =3D hi_a + hi_b + if lo' < lo_a then 1 else 0=0A= > fromInteger =3D integerToW64=0A= =0A= > instance Bits Zord64 where=0A= > W64{lo=3Dlo_a,hi=3Dhi_a} .&. W64{lo=3Dlo_b,hi=3Dhi_b} =3D = W64{lo=3Dlo', hi=3Dhi'}=0A= > where lo' =3D lo_a .&. lo_b=0A= > hi' =3D hi_a .&. hi_b=0A= > W64{lo=3Dlo_a,hi=3Dhi_a} .|. W64{lo=3Dlo_b,hi=3Dhi_b} =3D = W64{lo=3Dlo', hi=3Dhi'}=0A= > where lo' =3D lo_a .|. lo_b=0A= > hi' =3D hi_a .|. hi_b=0A= > shift w 0 =3D w=0A= > shift W64{lo=3Dlo,hi=3Dhi} x=0A= > | x > 63 =3D W64{lo=3D0,hi=3D0}=0A= > | x > 31 =3D W64{lo =3D 0, hi =3D shift lo (x-32)}=0A= > | x > 0 =3D W64{lo =3D shift lo x, hi =3D shift hi x .|. shift lo = (x-32)}=0A= > xor W64{lo=3Dalo,hi=3Dahi} W64{lo=3Dblo,hi=3Dbhi} =3D =0A= > W64{lo=3Dalo `xor` blo, hi=3Dahi `xor` bhi}=0A= =0A= > instance Integral Zord64 where=0A= > toInteger =3D w64ToInteger=0A= =0A= > instance Real Zord64=0A= > instance Enum Zord64=0A= =0A= ------=_NextPart_000_0007_01C30DC6.85F1AE00 Content-Type: application/octet-stream; name="Makefile" Content-Transfer-Encoding: quoted-printable Content-Disposition: attachment; filename="Makefile" PACKAGES=3D-package data=0A= HCFLAGS=3D$(PACKAGES) =0A= LINKFLAGS=3D$(PACKAGES)=0A= CPP=3D -cpp -DBEGIN_GHC_ONLY=3D'-}' -DEND_GHC_ONLY=3D'{-' \=0A= -DBEGIN_HUGS_ONLY=3D'{-' -DEND_HUGS_ONLY=3D'-}'=0A= HC =3D ghc=0A= =0A= SRCS=3DCrypto.hs ITest.hs=0A= OBJS=3DCrypto.o ITest.o=0A= =0A= all: ITest=0A= =0A= doc: Crypto.hs=0A= $(HC) -E Crypto.hs -o Crypto.hspp=0A= sed -e '/^#/d' Crypto.hspp > Crypto-hash.hspp=0A= haddock -h Crypto-hash.hspp=0A= rm Crypto.hspp Crypto-hash.hspp=0A= =0A= ITest: ITest.o=0A= $(HC) $(PACKAGES) -o ITest $(OBJS)=0A= =0A= Crypto.o: Crypto.hs=0A= $(HC) $(HCFLAGS) -fglasgow-exts $(CPP) -c $<=0A= =0A= %.o: %.hs=0A= $(HC) $(HCFLAGS) -c $<=0A= =0A= clean:=0A= rm -f *.o *.hi ITest=0A= =0A= depend:=0A= ghc -M $(PACKAGES) $(SRCS) $(CPP)=0A= sed "s/\([^\*\\]\)\.hi/\1.o/g" < Makefile > Makefile.new=0A= mv Makefile.new Makefile=0A= # DO NOT DELETE: Beginning of Haskell dependencies=0A= Crypto.o : Crypto.hs=0A= ITest.o : ITest.hs=0A= ITest.o : Crypto.o=0A= # DO NOT DELETE: End of Haskell dependencies=0A= ------=_NextPart_000_0007_01C30DC6.85F1AE00-- From Malcolm.Wallace@cs.york.ac.uk Tue Apr 29 14:33:39 2003 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Tue, 29 Apr 2003 14:33:39 +0100 Subject: [nhc-users] Re: Crytpo for nhc In-Reply-To: <000a01c30dbe$249b2300$1464a8c0@canterburysoftware.com> References: <000a01c30dbe$249b2300$1464a8c0@canterburysoftware.com> Message-ID: <20030429143339.5e291ee5.Malcolm.Wallace@cs.york.ac.uk> "Dominic Steinitz" writes: > I have been trying to write a Crypto library and so far it works with ghc > and hugs. > > Am I right in thinking I am going to struggle with nhc? It uses Word8 and > Word64 heavily. For example, cipher block chaining relies on xoring Word64. The things you mention are not a particular problem for nhc98. The only problem I encountered in the Crypto.hs code is that its use of the type class machinery is not Haskell'98 compliant. instance Bits [Bool] where ... is illegal in Haskell'98, because an instance head must be either a simple type name, or a type constructor applied to only type variables. (See the Report section 4.3.2) If ghc and Hugs permit this, then it is a non-standard extension to the language. Unfortunately, I don't immediately see an easy way to convert this construction into something more amenable. Regards, Malcolm