I'm new to Haskell. I've put together a basic Caesar Cipher, it works, but it's very messy and difficult to read.
caesarCipher :: Int -> String -> String
caesarCipher n xs = [shift n x | x <- xs]
shift n c = num2let ((let2num c + n) `mod` 26)
alphabet = ['a'..'z']
let2num c = head[ b | (a,b) <- zip alphabet [0..length alphabet], a==c]
num2let = (!!) alphabet
What is the "correct" way in Haskell to format functions that consist of multiple variables and expressions, and should I be considering the scope of the variables? And other than efficiency based suggestions have I made any other "major" mistakes?
This is my attempt:
caesarCipher n xs = let
shift n c = num2let ((let2num c + n) `mod` 26) where
alphabet = ['a'..'z']
let2num c = head[ b | (a,b) <- zip alphabet [0..length alphabet], a==c]
num2let = (!!) alphabet
in [shift n x | x <- xs]
I would first of all rewrite some functions. For example. zip alphabet [0 .. length alphabet] can be replaced with zip alphabet [0..], since the zip will stop from the moment one of the lists is exhausted. Making use of (!!) and head is often not good practice, since these functions are non-total: if the index is too large, or the list is empty, (!!) and head will error respectively.
We can define helper functions, for example for num2let:
import Data.Char(chr, ord)
num2let :: Int -> Char
num2let n = chr (n + ord 'a')
here num2let will map 0 to 'a', 1 to 'b', etc.
let2num can be done in a similar manner:
import Data.Char(ord)
let2num :: Char -> Int
let2num c = ord c - ord 'a'
So now we can define caesarCipher as:
caesarCipher :: Int -> String -> String
caesarCipher n = map (num2let . (`mod 26`) . (n+) . let2num)
So that would look in full as:
import Data.Char(chr, ord)
num2let :: Int -> Char
num2let n = chr (n + ord 'a')
let2num :: Char -> Int
let2num c = ord c - ord 'a'
caesarCipher :: Int -> String -> String
caesarCipher n = map (num2let . (`mod` 26) . (n+) . let2num)
The nice thing is that you can here reuse the let2num and num2let for other functions.
Normally top-level functions are separated with a blank line, and are given a signature. This is not necessary, but makes it usually more convenient to read.
Related
I'm trying to write a Caesar cipher but with only uppercase alphanumeric. Using ord or chr uses the whole ASCII table. How can accomplish this?
This is what I have so far:
alphabet = ['A'..'Z'] ++ ['0'..'9']
c2I = ord c - ord 'A'
i2C = chr (n + ord 'A')
the basic idea is to use mod to wrap around to the beginning.
Now it's not efficient (but hey you are using the most unsecure cipher so you might not care to much) but I'll show you using just the alphabet and indexing functions:
import Data.List (elemIndex)
alphabet :: [Char]
alphabet = ['A'..'Z'] ++ ['0'..'9']
ith :: Int -> Char
ith i = alphabet !! j
where j = i `mod` length alphabet
index :: Char -> Int
index c = case c `elemIndex` alphabet of
Just i -> i
Nothing -> error "not inalphabet"
encode :: Int -> String -> String
encode n xs = [ ith $ index x + n | x <- xs ]
this will give you
λ> encode 3 "ABCXYZ012789"
"DEF012345ABC"
now you probably will want to find a way using ord and chr - both works if you make a case distinction between A-Z and 0-9, because the ranges are:
65-90 for A-Z
48-57 for 0-9
so you cannot take a one formula without to many tricks
You should try but it's more math from here (you'll probably want something like ord c - ord 'A' for letters and 26 + ord c - ord '0' for digits to get it in the range 0-35 first.
If I was given a string like skhfbvqa, how would I generate the next string? For this example, it would be skhfbvqb, and the next string of that would be skhfbvqc, and so on. The given string (and the answer) will always be N characters long (in this case, N=8).
What I tried:
I tried to generate the entire (infinite) list of possible combinations, and get the required (next) string of the given string, but unsurprisingly, it's so slow, that I don't even get the answer for N=6.
I used list comprehension:
allStrings = [ c : s | s <- "" : allStrings, c <- ['a'..'z'] ]
main = do
input <- readFile "k.in"
putStrLn . head . tail . dropWhile (not . (==) input) . map reverse $ allStrings
(Please excuse my incredibly bad Haskell-ing :) Still a noob)
So my question is, how can I do this? If there are multiple methods, a comparison between them is much appreciated. Thanks!
Here's a version with base conversion (this way you could add and subtract arbitrarily if you like):
encode x base = encode' x [] where
encode' x' z | x' == 0 = z
| otherwise = encode' (div x' base) ((mod x' base):z)
decode num base =
fst $ foldr (\a (b,i) -> (b + a * base^i,i + 1)) (0,0) num
Output:
*Main> map (\x -> toEnum (x + 97)::Char)
$ encode (decode (map (\x -> fromEnum x - 97) "skhfbvqa") 26 + 1) 26
"skhfbvqb"
I would go and make a helper function f :: Integer -> String and one g :: String -> Integer, where f 1 = "a", ... f 27 = "aa", f 28 = "ab" and so on and the inverse g.
Then incrementString = f . succ . g
Note: I omitted the implementation of f on purpose for learning
Update
for a different approach you could define a increment with carry function inc' :: Char -> (Char, Bool), and then
incString :: String -> String
incString = reverse . incString'
where incString' [] = []
incString' (x:xs) = case inc' x of (x',True) -> x': incString' xs
(x',False) -> x':xs
Note: this function is not tail recursive!
I found this to work. It just uses pattern matching to see if the string begins with a z and adds an additional a accordingly.
incrementString' :: String -> String
incrementString' [] = ['a']
incrementString' ('z':xs) = 'a' : incrementString' xs
incrementString' (x:xs) = succ x : xs
incrementString :: String -> String
incrementString = reverse . incrementString' . reverse
Below I have defined a function that converts a list of base-3 digits to the corresponding numerical value. For example:
f "201" = (2 * 3^2) + (0 * 3^1) + (1 * 3^0) = 19
f "12" = 5
f "1202" = 47
f "120221" = 430
Here is a definition using comprehension:
f :: String -> Int
f str = sum (listToFinal (stringToTuples str))
Helper functions:
-- 1) converts "201" to "102"
reverse "str"
-- 2) converts "102" to 102
stringToInt :: String -> Int
stringToInt str = read str :: Int
-- 3) converts 102 to ['1','0','2']
intToList :: Int -> [Int]
intToList 0 = []
intToList x = intToList (x `div` 10) ++ [x `mod` 10]
-- 4) converts "201" to [(1,0),(0,1),(2,2)] using reverse, stringToInt, intToList
stringToTuples :: String -> [(Int,Int)]
stringToTuples str = zip (intToList (stringToInt (reverse str))) [0..]
-- 5) converts [(1,0),(0,1),(2,2)] to [1*3^0, 0*3^1, 2*3^2]
listToFinal :: [(Int,Int)] -> [Int]
listToFinal list = [ x * (3^y) | (x,y) <- list ]
Now I'd like to do it with recursion only (well, using basic & library functions too, of course).
An idea: I was thinking of taking the head of each element in the list and simply multiplying it with 3^(length of string - 1). The only problem is, with each recursive call the power of three would have to decrease by 1, e.g. given:
recursive_version "201" = (2 * 3^2) + (0 * 3^1) + (1 * 3^0)
How to implement this?
Here is a much simpler approach; note that, through the use of foldl, it's only "implicitly" recursive, though. For information, digitToInt is exported by Data.Char.
import Data.Char
import Data.List ( foldl' )
--- horner x xs : the value of polynomial 'xs' at point 'x'
horner :: Int -> [Int] -> Int
horner x = foldl' (\c1 c0 -> c1 * x + c0) 0
-- f s : the integer whose representation in base 3 is string 's'
f :: String -> Int
f = horner 3 . map digitToInt
When you define it recursively, the natural way to decrement the length is trimming the array from the head. For example:
base3 x = base3' x 0 where
base3' (d:ds) v = base3' ds $ v + d * 3 ^ length ds
base3' [] v = v
Modification may well be just an addition of 3 to the Char ascii value.
I have gone through several books and can't find a solution off the shelf.
(Returning the Char list can be to a different list variable.)
import Data.Char
shiftAscii :: String -> String
shiftAscii xs = map (chr.(+3).ord) xs
would do what you ask.
It works because map edits each character in the string using the supplied function.
ord converts the Char to its Int value
(+3) shifts the (ascii) by 3
chr converts back to a Char,
so chr.(+3).ord is those three strung together with function composition .
To be more flexible, you could write
shiftAsciiBy :: Int -> String -> String
shiftAsciiBy n = map (chr.(+ n).ord)
notice that shifting the ascii doesn't respect alphabet boundaries, so if you were needing this to do rot13 encoding or similar simple shift, you'd be better off with a hand-rolled shift function that only edits the alphabet
addAscii :: Int -> Char -> Char
addAscii n c | isUpper c = chr $ ((ord c - ord 'A' + n) `mod` 26) + ord 'A'
| isLower c = chr $ ((ord c - ord 'a' + n) `mod` 26) + ord 'a'
| otherwise = c
for example
['A'..'z']
"ABCDEFGHIJKLMNOPQRSTUVWXYZ[\\]^_`abcdefghijklmnopqrstuvwxyz"
and we shift just the alphabet ascii:
map (addAscii 5) ['A'..'z']
"FGHIJKLMNOPQRSTUVWXYZABCDE[\\]^_`fghijklmnopqrstuvwxyzabcde"
Here is my first Haskell program. What parts would you write in a better way?
-- Multiplication table
-- Returns n*n multiplication table in base b
import Text.Printf
import Data.List
import Data.Char
-- Returns n*n multiplication table in base b
mulTable :: Int -> Int -> String
mulTable n b = foldl (++) (verticalHeader n b w) (map (line n b w) [0..n])
where
lo = 2* (logBase (fromIntegral b) (fromIntegral n))
w = 1+fromInteger (floor lo)
verticalHeader :: Int -> Int -> Int -> String
verticalHeader n b w = (foldl (++) tableHeader columnHeaders)
++ "\n"
++ minusSignLine
++ "\n"
where
tableHeader = replicate (w+2) ' '
columnHeaders = map (horizontalHeader b w) [0..n]
minusSignLine = concat ( replicate ((w+1)* (n+2)) "-" )
horizontalHeader :: Int -> Int -> Int -> String
horizontalHeader b w i = format i b w
line :: Int -> Int -> Int -> Int -> String
line n b w y = (foldl (++) ((format y b w) ++ "|" )
(map (element b w y) [0..n])) ++ "\n"
element :: Int -> Int -> Int -> Int -> String
element b w y x = format (y * x) b w
toBase :: Int -> Int -> [Int]
toBase b v = toBase' [] v where
toBase' a 0 = a
toBase' a v = toBase' (r:a) q where (q,r) = v `divMod` b
toAlphaDigits :: [Int] -> String
toAlphaDigits = map convert where
convert n | n < 10 = chr (n + ord '0')
| otherwise = chr (n + ord 'a' - 10)
format :: Int -> Int -> Int -> String
format v b w = concat spaces ++ digits ++ " "
where
digits = if v == 0
then "0"
else toAlphaDigits ( toBase b v )
l = length digits
spaceCount = if (l > w) then 0 else (w-l)
spaces = replicate spaceCount " "
Here are some suggestions:
To make the tabularity of the computation more obvious, I would pass the list [0..n] to the line function rather than passing n.
I would further split out the computation of the horizontal and vertical axes so that they are passed as arguments to mulTable rather than computed there.
Haskell is higher-order, and almost none of the computation has to do with multiplication. So I would change the name of mulTable to binopTable and pass the actual multiplication in as a parameter.
Finally, the formatting of individual numbers is repetitious. Why not pass \x -> format x b w as a parameter, eliminating the need for b and w?
The net effect of the changes I am suggesting is that you build a general higher-order function for creating tables for binary operators. Its type becomes something like
binopTable :: (i -> String) -> (i -> i -> i) -> [i] -> [i] -> String
and you wind up with a much more reusable function—for example, Boolean truth tables should be a piece of cake.
Higher-order and reusable is the Haskell Way.
You don't use anything from import Text.Printf.
Stylistically, you use more parentheses than necessary. Haskellers tend to find code more readable when it's cleaned of extraneous stuff like that. Instead of something like h x = f (g x), write h = f . g.
Nothing here really requires Int; (Integral a) => a ought to do.
foldl (++) x xs == concat $ x : xs: I trust the built-in concat to work better than your implementation.
Also, you should prefer foldr when the function is lazy in its second argument, as (++) is – because Haskell is lazy, this reduces stack space (and also works on infinite lists).
Also, unwords and unlines are shortcuts for intercalate " " and concat . map (++ "\n") respectively, i.e. "join with spaces" and "join with newlines (plus trailing newline)"; you can replace a couple things by those.
Unless you use big numbers, w = length $ takeWhile (<= n) $ iterate (* b) 1 is probably faster. Or, in the case of a lazy programmer, let w = length $ toBase b n.
concat ( (replicate ((w+1)* (n+2)) "-" ) == replicate ((w+1) * (n+2)) '-' – not sure how you missed this one, you got it right just a couple lines up.
You do the same thing with concat spaces, too. However, wouldn't it be easier to actually use the Text.Printf import and write printf "%*s " w digits?
Norman Ramsey gave excellent high-level (design) suggestions; Below are some low-level ones:
First, consult with HLint. HLint is a friendly program that gives you rudimentary advice on how to improve your Haskell code!
In your case HLint gives 7 suggestions. (mostly about redundant brackets)
Modify your code according to HLint's suggestions until it likes what you feed it.
More HLint-like stuff:
concat (replicate i "-"). Why not replicate i '-'?
Consult with Hoogle whenever there is reason to believe that a function you need is already available in Haskell's libraries. Haskell comes with tons of useful functions so Hoogle should come in handy quite often.
Need to concatenate strings? Search for [String] -> String, and voila you found concat. Now go replace all those folds.
The previous search also suggested unlines. Actually, this even better suits your needs. It's magic!
Optional: pause and thank in your heart to Neil M for making Hoogle and HLint, and thank others for making other good stuff like Haskell, bridges, tennis balls, and sanitation.
Now, for every function that takes several arguments of the same type, make it clear which means what, by giving them descriptive names. This is better than comments, but you can still use both.
So
-- Returns n*n multiplication table in base b
mulTable :: Int -> Int -> String
mulTable n b =
becomes
mulTable :: Int -> Int -> String
mulTable size base =
To soften the extra characters blow of the previous suggestion: When a function is only used once, and is not very useful by itself, put it inside its caller's scope in its where clause, where it could use the callers' variables, saving you the need to pass everything to it.
So
line :: Int -> Int -> Int -> Int -> String
line n b w y =
concat
$ format y b w
: "|"
: map (element b w y) [0 .. n]
element :: Int -> Int -> Int -> Int -> String
element b w y x = format (y * x) b w
becomes
line :: Int -> Int -> Int -> Int -> String
line n b w y =
concat
$ format y b w
: "|"
: map element [0 .. n]
where
element x = format (y * x) b w
You can even move line into mulTable's where clause; imho, you should.
If you find a where clause nested inside another where clause troubling, then I suggest to change your indentation habits. My recommendation is to use consistent indentation of always 2 or always 4 spaces. Then you can easily see, everywhere, where the where in the other where is at. ok
Below's what it looks like (with a few other changes in style):
import Data.List
import Data.Char
mulTable :: Int -> Int -> String
mulTable size base =
unlines $
[ vertHeaders
, minusSignsLine
] ++ map line [0 .. size]
where
vertHeaders =
concat
$ replicate (cellWidth + 2) ' '
: map horizontalHeader [0 .. size]
horizontalHeader i = format i base cellWidth
minusSignsLine = replicate ((cellWidth + 1) * (size + 2)) '-'
cellWidth = length $ toBase base (size * size)
line y =
concat
$ format y base cellWidth
: "|"
: map element [0 .. size]
where
element x = format (y * x) base cellWidth
toBase :: Integral i => i -> i -> [i]
toBase base
= reverse
. map (`mod` base)
. takeWhile (> 0)
. iterate (`div` base)
toAlphaDigit :: Int -> Char
toAlphaDigit n
| n < 10 = chr (n + ord '0')
| otherwise = chr (n + ord 'a' - 10)
format :: Int -> Int -> Int -> String
format v b w =
spaces ++ digits ++ " "
where
digits
| v == 0 = "0"
| otherwise = map toAlphaDigit (toBase b v)
spaces = replicate (w - length digits) ' '
0) add a main function :-) at least rudimentary
import System.Environment (getArgs)
import Control.Monad (liftM)
main :: IO ()
main = do
args <- liftM (map read) $ getArgs
case args of
(n:b:_) -> putStrLn $ mulTable n b
_ -> putStrLn "usage: nntable n base"
1) run ghc or runhaskell with -Wall; run through hlint.
While hlint doesn't suggest anything special here (only some redundant brackets), ghc will tell you that you don't actually need Text.Printf here...
2) try running it with base = 1 or base = 0 or base = -1
If you want multiline comments use:
{- A multiline
comment -}
Also, never use foldl, use foldl' instead, in cases where you are dealing with large lists which must be folded. It is more memory efficient.
A brief comments saying what each function does, its arguments and return value, is always good. I had to read the code pretty carefully to fully make sense of it.
Some would say if you do that, explicit type signatures may not be required. That's an aesthetic question, I don't have a strong opinion on it.
One minor caveat: if you do remove the type signatures, you'll automatically get the polymorphic Integral support ephemient mentioned, but you will still need one around toAlphaDigits because of the infamous "monomorphism restriction."