
On Wed, Feb 23, 2005 at 12:27:19AM +0000, Terrence Brannon wrote:
Hi, I am getting into Haskell so I decided to convert a Perl module of mine:
http://cpan.uwinnipeg.ca/htdocs/Crypt-Discordian/Crypt/Discordian.html
into Haskell. I was pleased at the cleanliness and conciseness of the Haskell code. However, I am sure that it can be improved on and am soliciting any feedback you may have about this module.
Thanks, metaperl on #haskell
module Crypt_Discordian where
import List
vowel_list = "aeiouAEIOU"
is_vowel c = c `elem` vowel_list
move_vowels lis = move_vowels' lis [] []
move_vowels' [] c v = v ++ c move_vowels' (x:xs) c v | is_vowel x = move_vowels' xs c (x:v) | otherwise = move_vowels' xs (x:c) v
remove_spaces str = filter (\x -> x /= ' ') str
encrypt str = List.sort $ move_vowels $ remove_spaces str
How about
module CryptDiscordian where
import List
vowels = "aeiouAEIOU" isVowel = (flip elem) vowel_list
moveVowels xs = filter (not . isSpace) $ (filter (not . isVowel) xs ++ filter (is_vowel) xs)
encryptDiscordian xs = map chr $ sort $ map (ord . toLower) $ reverse $ moveVowels xs
[snip description of algorithm] Obviously, if it is implemented differently it won't be the Discordian encryption anymore, now will it? Note that my version is more conforming than yours, as you don't convert to numbers and back... Unfortunately, the algorithm doesn't state how to deal with capitalization, so I chose to just map to lowercase... Doei, Arthur. -- /\ / | arthurvl@cs.uu.nl | Work like you don't need the money /__\ / | A friend is someone with whom | Love like you have never been hurt / \/__ | you can dare to be yourself | Dance like there's nobody watching