{-# LANGUAGE OverloadedStrings #-} module Network.URI.Charset(resolveCharset, convertCharset) where import Data.Text (Text) import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as B import Data.Text.Encoding resolveCharset :: [String] -> ByteString -> (String, Either Text ByteString) resolveCharset (mime:('c':'h':'a':'r':'s':'e':'t':'=':charset):_) response = (mime, Left $ convertCharset charset $ B.toStrict response) resolveCharset (mime:_:params) response = resolveCharset (mime:params) response resolveCharset [mime] response = (mime, Right $ response) resolveCharset [] response = ("text/plain", Left "Filetype unspecified") convertCharset "iso-8859-1" = decodeLatin1 convertCharset "latin1" = decodeLatin1 convertCharset "us-ascii" = decodeUtf8 convertCharset "utf-8" = decodeUtf8 convertCharset "utf-16be" = decodeUtf16BE convertCharset "utf-16le" = decodeUtf16LE convertCharset "utf-16" = decodeUtf16LE convertCharset "utf-32be" = decodeUtf32BE convertCharset "utf-32le" = decodeUtf32LE convertCharset "utf-32" = decodeUtf32LE convertCharset _ = \_ -> "Unsupported text encoding!" charsets :: [Text] charsets = ["iso-8859-1", "latin1", "us-ascii", "utf-8", "utf-16be", "utf-16le", "utf-16", "utf-32be", "utf-32le", "utf-32"]