Skip to content

Instantly share code, notes, and snippets.

@matsubara0507
Last active November 23, 2015 07:22
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save matsubara0507/3b3e58a11fd51f4e92bc to your computer and use it in GitHub Desktop.
Save matsubara0507/3b3e58a11fd51f4e92bc to your computer and use it in GitHub Desktop.
Functions for Crypto of CTF
module Crypto where
import Data.List
import Data.Char
import qualified Data.Map as Map
rot :: Int -> [Char] -> [Char]
rot n s = map (rot' (['a'..'z'] ++ ['A'..'Z'])) s
where
rot' alps c
| Just i <- elemIndex c alps = alps !! ((i + n) `mod` (length alps))
| otherwise = c
morse :: [Char] -> Char
morse s
| Just c <- Map.lookup s hashmap = c
| otherwise = '?'
where
patterns = [".-","-...","-.-.","-..",".","..-.","--.","....","..",
".---","-.-",".-..","--","-.","---",".--.","--.-",".-.",
"...","-","..-","...-",".--","-..-","-.--","--..","..--.-"]
hashmap = Map.fromList $ zip patterns (['a'..'z']++['_'])
splitN :: Int -> [a] -> [[a]]
splitN n as = loop (splitAt n as)
where
loop :: ([a],[a]) -> [[a]]
loop (a,[]) = [a]
loop (a,as') = a:(loop $ splitAt n as')
hex2int :: [Char] -> Int
hex2int [h1,h2] = 16 * (f h1) + (f h2)
where
f c = case c of
'0' -> 0
'1' -> 1
'2' -> 2
'3' -> 3
'4' -> 4
'5' -> 5
'6' -> 6
'7' -> 7
'8' -> 8
'9' -> 9
'A' -> 10
'B' -> 11
'C' -> 12
'D' -> 13
'E' -> 14
'F' -> 15
_ -> error (c : " is not hex")
tr :: (Char,Char) -> String -> String
tr (c,c') s = map (\x -> if x == c then c' else x) s
asciiRot :: Int -> Char -> Char
asciiRot n = chr . (+ n) . ord
sqrtInteger :: Integer -> Maybe Integer
sqrtInteger num = loop digit (10,5,-1) 0
where
digit = (^) 10 $ (+) (-1) $ (`div` 2) $ (+) 1 $ length $ show num
loop :: Integer -> (Integer, Integer, Integer) -> Integer -> Maybe Integer
loop 0 _ r = if r^2 == num then Just r else Nothing
loop d (l,n,s) r
| num'^2 > num && l > n = loop d (n,(n+s)`div`2,s) r
| num'^2 < num && s < n = loop d (l,(l+n)`div`2,n) r
| otherwise = loop (d`div`10) (10,5,-1) num'
where num' = d * n + r
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment