[Haskell-cafe] module Crypt_Discordian - code critique requested

Terrence Brannon bauhaus at metaperl.com
Tue Feb 22 19:27:19 EST 2005


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.



More information about the Haskell-Cafe mailing list