module Codec.Binary.Base64.String (encode, decode) where
import Data.Bits (shiftL, shiftR, (.&.), (.|.))
import Data.Char (ord, chr, isAscii, isAlphaNum, isUpper, isLower, isDigit)
import Data.List (intersperse)
chars_per_line :: Int
chars_per_line = 64
encode :: String -> String
encode = concat . intersperse "\n" . splits chars_per_line . enc
enc :: String -> String
enc (c1:c2:c3:cs) = toChar (o1 `shiftR` 2)
: toChar (((o1 `shiftL` 4) .&. 0x30)
.|. (o2 `shiftR` 4))
: toChar (((o2 `shiftL` 2) .&. 0x3C)
.|. (o3 `shiftR` 6))
: toChar (o3 .&. 0x3F)
: enc cs
where o1 = ord c1
o2 = ord c2
o3 = ord c3
enc [c1, c2] = toChar (o1 `shiftR` 2)
: toChar (((o1 `shiftL` 4) .&. 0x30)
.|. (o2 `shiftR` 4))
: toChar ((o2 `shiftL` 2) .&. 0x3C)
: "="
where o1 = ord c1
o2 = ord c2
enc [c1] = toChar (o1 `shiftR` 2)
: toChar ((o1 `shiftL` 4) .&. 0x30)
: "=="
where o1 = ord c1
enc "" = ""
toChar :: Int -> Char
toChar n | n <= 25 = chr (ord 'A' + n)
| n <= 51 = chr (ord 'a' + n 26)
| n <= 61 = chr (ord '0' + n 52)
| n == 62 = '+'
| n == 63 = '/'
| otherwise
= error ("toChar: Can't happen: Bad input: " ++ show n)
decode :: String -> String
decode = dec . filter valid
where valid c = isAscii c
&& (isAlphaNum c || c == '+' || c == '/' || c == '=')
dec :: String -> String
dec "" = ""
dec ('=':_) = ""
dec (_:'=':_) = ""
dec (c1:c2:'=':_)
= take 1 $ dec [c1, c2, 'A', 'A']
dec (c1:c2:c3:'=':_)
= take 2 $ dec [c1, c2, c3, 'A']
dec (c1:c2:c3:c4:cs)
= let x1 = fromChar c1
x2 = fromChar c2
x3 = fromChar c3
x4 = fromChar c4
in
chr ((x1 `shiftL` 2) .|. (x2 `shiftR` 4))
: chr (((x2 `shiftL` 4) .&. 0xF0) .|. (x3 `shiftR` 2))
: chr (((x3 `shiftL` 6) .&. 0xC0) .|. x4)
: dec cs
dec [_] = ""
dec [_, _] = ""
dec [_, _, _] = ""
fromChar :: Char -> Int
fromChar c
| isUpper c = ord c ord 'A'
| isLower c = ord c ord 'a' + 26
| isDigit c = ord c ord '0' + 52
| c == '+' = 62
| c == '/' = 63
| otherwise = error ("fromChar: Can't happen: Bad input: " ++ show c)
splits :: Int -> [a] -> [[a]]
splits _ [] = []
splits n xs = case splitAt n xs of
(ys, zs) -> ys:splits n zs