[Haskell-cafe] Re: Solitaire cipher

Jón Fairbairn jon.fairbairn at cl.cam.ac.uk
Tue Oct 24 13:57:43 EDT 2006


jim burton <jim at sdf-eu.org> writes:

In addition to Chris's comments, here are some more:

> data Card = Clubs Int | Spades Int | Diamonds Int | Hearts Int | JokerA |
> JokerB 

They aren't really Ints; better to define something like

> data FaceValue = Ace | F2 | F3 | F4 | F5 | F6 | F7 | F8 | F9 | F10
>                | Jack | Queen | King

and possibly derive Enum (which unfortunately would give the
the "wrong" values, but that can be got around).

>             deriving (Show, Eq)
> type Deck = [Card]
> --cardval - clubs are face value, diamonds plus 13, and so on - Jokers are
> both 53

I'd be inclined to define an Enum instance rather than
cardval directly, but define cardval as an auxilliary
function that scrunches both jokers to the same value.

> isJoker        :: Card -> Bool
> isJoker JokerA = True
> isJoker JokerB = True
> isJoker _      = False

Since you've defined an instance of Eq, you can use 

> isJoker c = c == JokerA || c == JokerB

> --take a card to a letter 
> card2char :: Card -> Char
> card2char c = case c of
>                       (Clubs i)    -> int2alpha $ cardval c --can case fall
> through in haskell?

It's defined to, but you don't need a case clause as you can
use cardval and mod.

> --take a letter to int, A=1, Z=26
> char2int :: Char -> Int
> char2int = (64 `subtract`) . (ord)

Better to use (ord 'A' - 1) if you are going to do it this
way.

> --take a letter to int, 1=A, Z=26
> int2alpha :: Int -> Char
> int2alpha = (chr) . (+64)

and again

> splitAtMb n l = let p = splitAt n l
>                    in if null $ fst p
>                       then Nothing
>                       else Just p

That was my mistake! Use the shorter, cleaner version I
posted after that one.

> in_fives l = foldr (\x y -> x++" "++y) [] $ unfoldr (splitAtMb 5)
>              (l ++ replicate (5 - length l `mod` 5) 'X') 

Putting the spaces in at this point is a mistake! Also see
what I said about length.

> --get an ordered deck
> newdeck :: Deck
> newdeck = suit 'c' ++ suit 'd' ++ suit 'h' ++ suit 's' ++ JokerA : JokerB :
> []
>     where suit s = case s of
>                           'c' -> [Clubs i | i <- [1..13]]
>                           's' -> [Spades i | i <- [1..13]]
>                           'd' -> [Diamonds i | i <- [1..13]]
>                           'h' -> [Hearts i | i <- [1..13]]

That seems overly complicated. With an Enum instance, you'd just do

> newdeck = [Club Ace .. JokerB]

or better, with an instance of Bounded too,

> newdeck = [minBound .. maxBound]

Of course, you'd have to write toEnum to do the work, but
I'd do it something like

>     toEnum 54 = JokerB
>     toEnum 53 = JokerA
>     toEnum n = [Club, Diamond, Heart, Spade]!!suit $ (toEnum (val+1))
>                where (suit, val) = (n-1) `divMod` 13

Comments from now on are a bit less thought through... I
think there are better ways to do some of these operations,
but I'm not going to present them, just nitpick a bit
instead.

> --key the deck ready to provide a keystream - move JokerA down one place,
> --JokerB down 2 places, perform a triplecut then a countcut
> keydeck :: Deck -> Deck
> keydeck = countcut. triplecut . (movedown JokerB) . (movedown JokerB) .
> (movedown JokerA)
> 
> --bump a card down by one place in a deck, treating the deck as circular so
> if the card is
> -- last in the deck it becomes 2nd to front not 1st
> movedown     :: Eq a => a -> [a] -> [a]
> movedown c d = if c == last d

that looks like an unnecessary pass over the list

>                then head d : c : init (tail d)
>                else top ++ bot!!1 : c : (tail (tail bot))
>                where splt = splitAt (locate c d) d
>                      top = fst splt
>                      bot = snd splt

you can write 

> where (top,bot) = splitAt ...  But how about List.break?

And if you know that bot is going to have enough elements

> where (top, card1:card2:rest) = break ... 

-- 
Jón Fairbairn                                 Jon.Fairbairn at cl.cam.ac.uk



More information about the Haskell-Cafe mailing list