
On Sat, Jan 10, 2004 at 11:09:27AM -0000, Dominic Steinitz wrote:
I would like to annouce a new release of the Haskell Cryptographic Library (1.0.1). See http://www.haskell.org/crypto/ReadMe.html for more details.
With the accompanying patch, this library also works with the most recent (Nov 2003) release of Hugs. There are two issues: - Hugs implements the monomorphism restriction differently from H98; the workaround is to add some type signatures. - Hugs doesn't support GHC's fancy type synonyms. You might also need to use System.IO.openBinaryFile in places. ----------------------------------------------------------------------- diff -ur crypto/Codec/ASN1/ASN1.hs crypto-new/Codec/ASN1/ASN1.hs --- crypto/Codec/ASN1/ASN1.hs 2004-01-10 10:33:03.000000000 +0000 +++ crypto-new/Codec/ASN1/ASN1.hs 2004-01-12 11:11:26.000000000 +0000 @@ -578,9 +578,6 @@ decode :: WrapMonad m => Handle -> m (Int,a) decode' :: WrapMonad m => Handle -> Int -> m a -type BERParser a = WrapMonad m => Handle -> m a -type BERParser' a = WrapMonad m => Handle -> Int -> m a - data TagType = Universal | Application | Context | Private deriving (Eq, Enum, Show, Read, Ord) @@ -630,7 +627,7 @@ t = shift (fromIntegral (fromEnum tagType)) 6 c = shift (fromIntegral (fromEnum tagCons)) 5 -fromTag :: BERParser (Int,TagCons,Tag) +fromTag :: WrapMonad m => Handle -> m (Int,TagCons,Tag) fromTag h = do y <- get' h let x :: ConcreteOctet @@ -645,7 +642,7 @@ let longform = fromIntegral (octetStreamToInteger 128 xs) in return (length xs + 1,c,(t,longform)) -getTagOctets :: BERParser OctetStream +getTagOctets :: WrapMonad m => Handle -> m OctetStream getTagOctets h = do x <- get' h let y = fromIntegral (ord x) in @@ -670,7 +667,7 @@ longform x = (setBit (fromIntegral(length(y))) msb) : y y = toBase 256 x -fromLength :: BERParser (Int,Length) +fromLength :: WrapMonad m => Handle -> m (Int,Length) fromLength h = do y <- get' h let x :: ConcreteOctet @@ -687,7 +684,7 @@ Definite (octetStreamToInteger 256 xs) in return (length+1,longform) -getLengthOctets :: BERParser' OctetStream +getLengthOctets :: WrapMonad m => Handle -> Int -> m OctetStream getLengthOctets h l = if l <= 0 then return [] @@ -812,7 +809,7 @@ getSubId xs = Just $ span' endOfSubId xs endOfSubId = not . (flip testBit oidBitsPerOctet) -oidBitsPerOctet = 7 +oidBitsPerOctet = 7 :: Int span' :: (a -> Bool) -> [a] -> ([a],[a]) span' p [] @@ -1083,7 +1080,7 @@ otherwise -> error "fromASN: invalid primitive tag for [ASN]" -getOctets :: BERParser' OctetStream +getOctets :: WrapMonad m => Handle -> Int -> m OctetStream getOctets h l = if (l <= 0) then return [] @@ -1139,7 +1136,7 @@ return (m,(Constructed' t bs)) decode' = error "decode': not supported for ASN" -decodeASNs :: BERParser' [ASN] +decodeASNs :: WrapMonad m => Handle -> Int -> m [ASN] decodeASNs h curLen | curLen < 0 = error "decodeASNs: trying to decode a negative number of octets" | curLen == 0 = return [] diff -ur crypto/Test.hs crypto-new/Test.hs --- crypto/Test.hs 2003-06-07 13:45:22.000000000 +0100 +++ crypto-new/Test.hs 2004-01-12 10:59:45.000000000 +0000 @@ -106,11 +106,11 @@ -- Test from http://www.itl.nist.gov/fipspubs/fip81.htm -key = 0x0123456789abcdef -iv = 0x1234567890abcdef +key = 0x0123456789abcdef :: Word64 +iv = 0x1234567890abcdef :: Word64 expectedDES = [0xe5c7cdde872bf27c, 0x43e934008c389c0f, - 0x683788499a7c05f6] + 0x683788499a7c05f6] :: [Word64] plainText = "Now is the time for all " -- Pad using PKCS#5 so only take the first 3 blocks of the ciphertext.