module Network.DomainAuth.Mail.Types where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
import Data.Char
import Data.Sequence
type RawMail = ByteString
type = ByteString
type RawBody = ByteString
type RawField = ByteString
type RawFieldKey = ByteString
type RawFieldValue = ByteString
type RawBodyChunk = ByteString
data Mail = Mail {
:: Header
, Mail -> Body
mailBody :: Body
} deriving (Mail -> Mail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mail -> Mail -> Bool
$c/= :: Mail -> Mail -> Bool
== :: Mail -> Mail -> Bool
$c== :: Mail -> Mail -> Bool
Eq,Int -> Mail -> ShowS
[Mail] -> ShowS
Mail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mail] -> ShowS
$cshowList :: [Mail] -> ShowS
show :: Mail -> String
$cshow :: Mail -> String
showsPrec :: Int -> Mail -> ShowS
$cshowsPrec :: Int -> Mail -> ShowS
Show)
isEmpty :: Body -> Bool
isEmpty :: Body -> Bool
isEmpty = (forall a. Eq a => a -> a -> Bool
== forall a. Seq a
empty)
type = [Field]
data Field = Field {
Field -> ByteString
fieldSearchKey :: CanonFieldKey
, Field -> ByteString
fieldKey :: FieldKey
, Field -> FieldValue
fieldValue :: FieldValue
} deriving (Field -> Field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c== :: Field -> Field -> Bool
Eq,Int -> Field -> ShowS
Header -> ShowS
Field -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: Header -> ShowS
$cshowList :: Header -> ShowS
show :: Field -> String
$cshow :: Field -> String
showsPrec :: Int -> Field -> ShowS
$cshowsPrec :: Int -> Field -> ShowS
Show)
type CanonFieldKey = ByteString
type FieldKey = ByteString
type FieldValue = [ByteString]
type Body = Seq ByteString
canonicalizeKey :: FieldKey -> CanonFieldKey
canonicalizeKey :: ByteString -> ByteString
canonicalizeKey = (Char -> Char) -> ByteString -> ByteString
BS.map Char -> Char
toLower