module Network.IRC.CTCP
(
CTCPByteString
, getUnderlyingByteString
, toCTCP
, fromCTCP
, encodeCTCP
, decodeCTCP
, isCTCP
, asCTCP
, orCTCP
) where
import Data.ByteString (ByteString, pack, singleton, unpack)
import Data.List (mapAccumL)
import Data.Maybe (catMaybes, fromMaybe)
import Data.Text (Text, splitOn)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Tuple (swap)
import qualified Data.ByteString as B
import qualified Data.Text as T
newtype CTCPByteString = CBS ByteString
deriving (Eq, Show)
getUnderlyingByteString :: CTCPByteString -> ByteString
getUnderlyingByteString (CBS bs) = bs
toCTCP :: Text -> [Text] -> CTCPByteString
toCTCP cmd args = encodeCTCP . encodeUtf8 . T.unwords $ cmd : args
encodeCTCP :: ByteString -> CTCPByteString
encodeCTCP bs = CBS $ B.concat [ singleton soh
, escape bs
, singleton soh
]
where escape = B.concatMap escape'
escape' x = case lookup x encodings of
Just x' -> pack [esc, x']
Nothing -> singleton x
fromCTCP :: CTCPByteString -> (Text, [Text])
fromCTCP bs = case splitOn (T.pack " ") . decodeUtf8 . decodeCTCP $ bs of
(cmd : args) -> (cmd, args)
_ -> (T.pack "", [])
decodeCTCP :: CTCPByteString -> ByteString
decodeCTCP (CBS bs) = unescape . B.tail . B.init $ bs
where unescape = pack . catMaybes . snd . mapAccumL step False . unpack
step True x = (False, Just . fromMaybe x $ lookup x decodings)
step False 0o020 = (True, Nothing)
step _ x = (False, Just x)
soh :: Integral i => i
soh = 0o001
esc :: Integral i => i
esc = 0o020
encodings :: Integral i => [(i, i)]
encodings = [ (0o000, 0o060)
, (0o012, 0o156)
, (0o015, 0o162)
, (0o020, 0o020)
]
decodings :: Integral i => [(i, i)]
decodings = map swap encodings
isCTCP :: ByteString -> Bool
isCTCP bs = and $ (B.length bs >= 2) : (B.head bs == soh) : (B.last bs == soh) : map (flip B.notElem bs . fst) encodings
asCTCP :: ByteString -> Maybe CTCPByteString
asCTCP bs = if isCTCP bs
then Just $ CBS bs
else Nothing
orCTCP :: (ByteString -> a) -> (CTCPByteString -> a) -> ByteString -> a
orCTCP f g bs = maybe (f bs) g (asCTCP bs)