how about this, for wordSize? I used quickcheck to verify that my 
wordSize2 is the same as yours.

Actually, it's not! if you allow negative integers in the list, it's not 
at any rate. ("falsifiable after 50 tries")

I haven't thought through what this means... if your function isn't quite 
right, or mine, or it doesn't really matter.

Also I would be curious to see this quickchecked but not allowing negative 
integers in the list if someone can show me how to do that.

Also, I commented out intToBinWord because intToBin isn't in prelude nor 
in any library I could track down and I'm not sure what it was supposed to 
do.

thomas.

import Data.List
import Data.Maybe
import Test.QuickCheck

wordSize :: [Int] -> Int
wordSize xs = head (dropWhile (<(length xs)) $ iterate (*2) 8)

wordSize2 :: [Int] -> Int
wordSize2 xs = fromJust $ find (>(length xs)) $ iterate (*2) 8

main = quickCheck $ \xs -> wordSize2 ( xs :: [Int]) == wordSize xs

{-
intToBinWord :: Int -> [Int]
intToBinWord n = reverse (take elements (xs ++ repeat 0))
  where
  xs = reverse (intToBin n)
  elements = wordSize xs
-}






PR Stanley <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED]
10/12/2007 03:10 PM

To
haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] more functions to evaluate






Hi folks
Any comments and/or criticisms no matter how trivial on the following 
please:

                 wordSize :: [Int] -> Int
                 wordSize xs = head (dropWhile (<(length xs)) $ iterate 
(*2) 8)

                 intToBinWord :: Int -> [Int]
                 intToBinWord n = reverse (take elements (xs ++ repeat 0))
                   where
                   xs = reverse (intToBin n)
                   elements = wordSize xs

Thanks, Paul

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to