[Haskell-beginners] State help request

David McBride toad3k at gmail.com
Sat Dec 8 17:42:08 CET 2012


I'm not completely sure how to run this to make sure it gives the right
answer, but I believe this is equivalent to what you had.

1.  Change runState to execState.  If you only need one tuple of what
runState returns, you can replace it with execState or evalState and
shorten code a bit.
2. I shortened the function you pass to foldl, by making it point free.  I
could have also changed it to foldr and gotten rid of the flip, but I'm not
sure if that would give the same answer.  If it does, you should do that.
3. Key was in your state, but it wasn't being mutated in any loop, so
instead, I just passed it into ksaStep' directly and let it use it without
having to fetch it on each loop.  Since you are only mutating the PRGA,
that should be the only thing in there.

ksa' :: Key -> PRGA
ksa' key = foldl (flip $ execState . ksaStep' key) (permId,0,0) [0..255]

ksaStep' :: Key -> Int -> State PRGA ()
ksaStep' key i = do
  (s,_,j) <- get

  let j' = (j + (s!i) + (key !! (i `mod` length(key)))) `mod` 256
      s' = s // [(i, s!j'), (j',s!i)]

  put $ (s',i,j')

That's not too bad, but
4. You are dangerously treading on the line where I believe it is
responsible to stop using primitive 'types' and start using
'newtypes/datas'.  In particular your Key type in this new code keeps
getting the length of the key on every ksaStep' call.  It might be wise to
add code like this:

data Key = Key {
  keyValue :: [Int],
  keyLen :: Int
}

That way, the length is computed once when the key is generated, and then
used for the rest of the program.  As a side benefit, your error messages
will be just a bit more helpful.

And man I just want to say how jealous I am.  I wish I could go to a ny
haskell group :(.

On Fri, Dec 7, 2012 at 11:03 PM, Joe <xe4mxee at gmail.com> wrote:

> Hi,
>
> below is an implementation of RC4, which I started after Andrew
> Gwozdziewycz from NY Hack & Tell encouraged the group to write it. I
> mostly followed the pseudocode on Wikipedia.
>
> I'd appreciate any feedback, but I'm most distressed by the KSA
> generation, and would like suggestions for making either version less
> nasty.
>
> Thanks.
>
>
> import Data.Bits
> import Data.Vector ((!),(//),Vector,fromList)
> import Data.Char
> import Control.Monad.State
>
> type PRGA = (Vector Int,Int,Int)
> type Key = [Int]
>
> -- identity permutation
> permId :: Vector Int
> permId = fromList [0..255]
>
> -- generate initial PRGA
> ksa :: Key -> PRGA
> ksa key = ksaStep permId key 0 0
>
> -- I really don't like passing the counter every time,
> ksaStep :: Vector Int -> Key -> Int -> Int -> PRGA
> ksaStep s _ 255 _ = (s,0,0)
> ksaStep s key i j = let j' = (j + (s!i) + (key !! (i `mod`
> keylength))) `mod` 256 in
>   ksaStep (s // [(i, s!j'), (j',s!i)]) key (i+1) j'
>   where keylength = length key
>
> -- but I tried wedging it into a State, and it's not any clearer
> ksa' :: Key -> PRGA
> ksa' key = genPRGA
>   where genPRGA = snd $ foldl (\s a -> snd $ runState (ksaStep' a) s)
> (key,(permId,0,0)) [0..255]
>
> ksaStep' :: Int -> State (Key,PRGA) ()
> ksaStep' i = do
>   (key, (s,_,j)) <- get
>   let j' = (j + (s!i) + (key !! (i `mod` length(key)))) `mod` 256
>       s' = s // [(i, s!j'), (j',s!i)]
>   put (key,(s',i,j'))
>
> -- a round of the PRGA
> prgaStep :: State PRGA Int
> prgaStep = do
>   (s,i,j) <- get
>   let i' = (i + 1) `mod` 256
>       j' = (j + (s!i')) `mod` 256
>       s' = s // [(i',s!j'), (j',s!i')]
>   put (s',i',j')
>   return (s!((s'!i' + s'!j') `mod` 256))
>
> keyStream :: PRGA -> [Int]
> keyStream p = let (i,p') = runState prgaStep p
>                in i : keyStream p'
>
>
> crypt :: Key -> [Int] -> [Int]
> crypt k m = zipWith xor m $ keyStream $ ksa k
>
>
> pwCrypt :: String -> String -> [Int]
> pwCrypt ks ms = crypt key msg
>   where key = map ord ks
>         msg = map ord ms
>
> pwDecrypt :: String -> [Int] -> String
> pwDecrypt k c = map chr $ crypt key c
>   where key = map ord k
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20121208/a6059e1a/attachment.htm>


More information about the Beginners mailing list