Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utilities for parsing a DMARC aggregated report, following RFC 7489. These functions also handle decompression (gzip or pkzip)
Synopsis
- dmarcFeedbackFromStrict :: ByteString -> Maybe Feedback
- dmarcFeedbackFromLazy :: ByteString -> Maybe Feedback
- dmarcFeedbackFromStream :: (MonadFail m, MonadIO m) => ByteStream m r -> m (Maybe Feedback)
- dmarcFeedbackFromXml :: Element -> Maybe Feedback
- data Feedback = Feedback {}
- data ReportMetadata = ReportMetadata {}
- data Record = Record {}
- data Row = Row {}
- data PolicyPublished = PolicyPublished {}
- data PolicyEvaluated = PolicyEvaluated {}
- data DkimAuth = DkimAuth {
- daResult :: AuthResult
- daDomain :: Text
- daSelector :: Text
- data SpfAuth = SpfAuth {
- saResult :: AuthResult
- saDomain :: Text
- data AuthResult
- type IpAddress = String
- data AlignmentMode
- data PolicyAction
- = NoPolicy
- | Quarantine
- | Reject
- uncompressStream :: (MonadFail m, MonadIO m) => ByteStream m r -> ByteStream m ()
Parsers
dmarcFeedbackFromStrict :: ByteString -> Maybe Feedback Source #
Parse a DMARC report from a strict ByteString
dmarcFeedbackFromLazy :: ByteString -> Maybe Feedback Source #
Parse a DMARC report from a lazy ByteString
dmarcFeedbackFromStream :: (MonadFail m, MonadIO m) => ByteStream m r -> m (Maybe Feedback) Source #
Parse a DMARC report from a ByteStream
Data types
data ReportMetadata Source #
Instances
Eq ReportMetadata Source # | |
Defined in Data.Mail.DMARC.Reports (==) :: ReportMetadata -> ReportMetadata -> Bool # (/=) :: ReportMetadata -> ReportMetadata -> Bool # | |
Read ReportMetadata Source # | |
Defined in Data.Mail.DMARC.Reports readsPrec :: Int -> ReadS ReportMetadata # readList :: ReadS [ReportMetadata] # | |
Show ReportMetadata Source # | |
Defined in Data.Mail.DMARC.Reports showsPrec :: Int -> ReportMetadata -> ShowS # show :: ReportMetadata -> String # showList :: [ReportMetadata] -> ShowS # |
data PolicyPublished Source #
Instances
Eq PolicyPublished Source # | |
Defined in Data.Mail.DMARC.Reports (==) :: PolicyPublished -> PolicyPublished -> Bool # (/=) :: PolicyPublished -> PolicyPublished -> Bool # | |
Read PolicyPublished Source # | |
Defined in Data.Mail.DMARC.Reports | |
Show PolicyPublished Source # | |
Defined in Data.Mail.DMARC.Reports showsPrec :: Int -> PolicyPublished -> ShowS # show :: PolicyPublished -> String # showList :: [PolicyPublished] -> ShowS # |
data PolicyEvaluated Source #
Instances
Eq PolicyEvaluated Source # | |
Defined in Data.Mail.DMARC.Reports (==) :: PolicyEvaluated -> PolicyEvaluated -> Bool # (/=) :: PolicyEvaluated -> PolicyEvaluated -> Bool # | |
Read PolicyEvaluated Source # | |
Defined in Data.Mail.DMARC.Reports | |
Show PolicyEvaluated Source # | |
Defined in Data.Mail.DMARC.Reports showsPrec :: Int -> PolicyEvaluated -> ShowS # show :: PolicyEvaluated -> String # showList :: [PolicyEvaluated] -> ShowS # |
DkimAuth | |
|
SpfAuth | |
|
data AuthResult Source #
NoAuth | no policy published |
AuthPass | successful authentication |
AuthFail | authentication failed |
TempError | temporary error in resolving the policy |
PermError | permanent error in resolving the policy |
AuthNeutral | ??? (DKIM only) |
AuthPolicy | ??? (DKIM only) |
SoftFail | auth failed, but won't reject (SPF only) |
Instances
Eq AuthResult Source # | |
Defined in Data.Mail.DMARC.Reports (==) :: AuthResult -> AuthResult -> Bool # (/=) :: AuthResult -> AuthResult -> Bool # | |
Read AuthResult Source # | |
Defined in Data.Mail.DMARC.Reports readsPrec :: Int -> ReadS AuthResult # readList :: ReadS [AuthResult] # readPrec :: ReadPrec AuthResult # readListPrec :: ReadPrec [AuthResult] # | |
Show AuthResult Source # | |
Defined in Data.Mail.DMARC.Reports showsPrec :: Int -> AuthResult -> ShowS # show :: AuthResult -> String # showList :: [AuthResult] -> ShowS # |
data AlignmentMode Source #
Instances
Eq AlignmentMode Source # | |
Defined in Data.Mail.DMARC.Reports (==) :: AlignmentMode -> AlignmentMode -> Bool # (/=) :: AlignmentMode -> AlignmentMode -> Bool # | |
Read AlignmentMode Source # | |
Defined in Data.Mail.DMARC.Reports readsPrec :: Int -> ReadS AlignmentMode # readList :: ReadS [AlignmentMode] # | |
Show AlignmentMode Source # | |
Defined in Data.Mail.DMARC.Reports showsPrec :: Int -> AlignmentMode -> ShowS # show :: AlignmentMode -> String # showList :: [AlignmentMode] -> ShowS # |
data PolicyAction Source #
Instances
Eq PolicyAction Source # | |
Defined in Data.Mail.DMARC.Reports (==) :: PolicyAction -> PolicyAction -> Bool # (/=) :: PolicyAction -> PolicyAction -> Bool # | |
Read PolicyAction Source # | |
Defined in Data.Mail.DMARC.Reports readsPrec :: Int -> ReadS PolicyAction # readList :: ReadS [PolicyAction] # | |
Show PolicyAction Source # | |
Defined in Data.Mail.DMARC.Reports showsPrec :: Int -> PolicyAction -> ShowS # show :: PolicyAction -> String # showList :: [PolicyAction] -> ShowS # |
Utility
uncompressStream :: (MonadFail m, MonadIO m) => ByteStream m r -> ByteStream m () Source #
Uncompress gzip or pkzip stream. If it is neither gzipped or pkzipped, return the stream unmodified.