module Crypt_Discordian - code critique requested

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 {- The algorithm for Discordian text encryption is given at: http://www.principiadiscordia.com/book/78.php After implementing this, I realized that all the early steps are a farce. But anyway, here is the algorithm in case you don't enjoy tilting your head to read a page: Step 1. Write out message (HAIL ERIS) and put all vowels at the end (HLRSAIEI) Step 2. Reverse order (IEIASRLH) Step 3. Convert to numbers (9-5-9-1-19-18-12-8) Step 4. Put into numerical order (1-5-8-9-9-12-18-19) Step 5. Convert back to letter (AEHIILRS) This cryptographic cypher code is GUARANTEED TO BE 100% UNBREAKABLE .. so says the Principia Discordia. But I think we can generate and test to break it. Many thanks to kosmikus and Pseudonym for their help in developing this module -} -- Carter's Compass: I know I'm on the right track when, by deleting something, I'm adding functionality.

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

On Wed, Feb 23, 2005 at 08:46:23AM +0100, Arthur van Leeuwen wrote:
On Wed, Feb 23, 2005 at 12:27:19AM +0000, Terrence Brannon wrote:
[snip, encryptia discordia]>
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
Which won't work, as it lacks an import Char. Doei, Arthur. (Still waking up, apparently) -- /\ / | 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

Arthur van Leeuwen
On Wed, Feb 23, 2005 at 08:46:23AM +0100, Arthur van Leeuwen wrote:
On Wed, Feb 23, 2005 at 12:27:19AM +0000, Terrence Brannon wrote:
[snip, encryptia discordia]>
How about
module CryptDiscordian where
import List
vowels = "aeiouAEIOU" isVowel = (flip elem) vowel_list
you use vowel_list but define vowels also, I believe isVowel is taking advantage of a curried version of elem. Correct? -- Carter's Compass: I know I'm on the right track when, by deleting something, I'm adding functionality.

On Wed, Feb 23, 2005 at 12:27:19AM +0000, Terrence Brannon wrote:
But anyway, here is the algorithm in case you don't enjoy tilting your head to read a page:
Step 1. Write out message (HAIL ERIS) and put all vowels at the end (HLRSAIEI)
Step 2. Reverse order (IEIASRLH)
Step 3. Convert to numbers (9-5-9-1-19-18-12-8)
Step 4. Put into numerical order (1-5-8-9-9-12-18-19)
Step 5. Convert back to letter (AEHIILRS)
This cryptographic cypher code is GUARANTEED TO BE 100% UNBREAKABLE
.. so says the Principia Discordia. But I think we can generate and test to break it.
Isn't it guaranteed unbreakable simply because there's no way to decrypt it? Since there isn't a one-to-one mapping of cyphertext to plaintext, I don't think it's actually a form of encryption. Basically it's the same as the sort function, which is also not invertible. -- David Roundy http://www.darcs.net

On Wed, 23 Feb 2005, David Roundy wrote:
On Wed, Feb 23, 2005 at 12:27:19AM +0000, Terrence Brannon wrote:
But anyway, here is the algorithm in case you don't enjoy tilting your head to read a page:
Step 1. Write out message (HAIL ERIS) and put all vowels at the end (HLRSAIEI)
Step 2. Reverse order (IEIASRLH)
Step 3. Convert to numbers (9-5-9-1-19-18-12-8)
Step 4. Put into numerical order (1-5-8-9-9-12-18-19)
Step 5. Convert back to letter (AEHIILRS)
This cryptographic cypher code is GUARANTEED TO BE 100% UNBREAKABLE
.. so says the Principia Discordia. But I think we can generate and test to break it.
Isn't it guaranteed unbreakable simply because there's no way to decrypt it? Since there isn't a one-to-one mapping of cyphertext to plaintext, I don't think it's actually a form of encryption. Basically it's the same as the sort function, which is also not invertible.
yes, EXCEPT and EXPECT will get the same "encryption" ... ... and why is the order reversed (step 2) before the sorting (step 4) ?

Henning Thielemann
On Wed, 23 Feb 2005, David Roundy wrote:
Isn't it guaranteed unbreakable simply because there's no way to decrypt it? Since there isn't a one-to-one mapping of cyphertext to plaintext, I don't think it's actually a form of encryption. Basically it's the same as the sort function, which is also not invertible.
yes, EXCEPT and EXPECT will get the same "encryption" ...
... and why is the order reversed (step 2) before the sorting (step 4) ?
Yes, I guess you aren't familiar with the Discordians. They are a group of people who believe that spirituality is as much about disharmony as it is about harmony. So, in their primary book, Principia Discorida: http://principiadiscordia.com/ you never know what is serious and what is play. The wikipedia has more to say on them: http://en.wikipedia.org/wiki/Discordian -- Terrence Brannon, sundevil@livingcosmos.org, http://www.livingcosmos.org

Were I to write the same code as
Terrence Brannon
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
I would likely write
module Foo where
vowel_list = "aeiouAEIOU"
split_vowels = partition (`elem` vowel_list)
tuple_to_list t = fst t ++ snd t
remove_spaces = filter (/= ' ')
encrypt = List.sort . tuple_to_list . split_vowels . remove_spaces
instead. But I have this feeling that tuple_to_list is probably already in the library, I just missed it. The arbiters of good-Haskell-style can now enumerate the ways in which my code is 'bad' ;-) Jacques

On Wed, 23 Feb 2005, Jacques Carette wrote:
I would likely write
module Foo where
vowel_list = "aeiouAEIOU"
split_vowels = partition (`elem` vowel_list)
tuple_to_list t = fst t ++ snd t
remove_spaces = filter (/= ' ')
encrypt = List.sort . tuple_to_list . split_vowels . remove_spaces
instead. But I have this feeling that tuple_to_list is probably already in the library, I just missed it.
do you mean uncurry (++) ?
participants (5)
-
Arthur van Leeuwen
-
David Roundy
-
Henning Thielemann
-
Jacques Carette
-
Terrence Brannon