@@ 1,9 1,9 @@
module Email where
-import BasicPrelude
import Prelude ()
+import BasicPrelude
import Data.Char (isAscii, isAlphaNum)
-import Data.Functor ((<&>))
+import Data.Functor ((<&>), ($>))
import Control.Error
(headZ, lastZ, justZ, hush, exceptT)
import Data.Time.Clock (UTCTime)
@@ 29,8 29,7 @@ mboxFrom :: Atto.Parser ()
mboxFrom =
Atto.string (encodeUtf8 $ s"From ") *>
Atto.skipWhile (\c -> c /= 0x0D && c /= 0x0A) *>
- MIME.crlf *>
- pure ()
+ MIME.crlf $> ()
messageID :: Atto.Parser Text
messageID =
@@ 130,7 129,7 @@ extractThreadFromRefs domain =
((Just <$> extractThreadFromRef domain) <|> skipWord)
(Atto.many1 $ Atto.satisfy (==0x20))
where
- skipWord = Atto.skipWhile (/=0x20) *> pure Nothing
+ skipWord = Atto.skipWhile (/=0x20) $> Nothing
limitReferencesLength :: ByteString -> ByteString
limitReferencesLength refs = C8.unwords $ limit (C8.words refs)
@@ 218,13 217,12 @@ typeHeaders _ = id
mkMessageID :: MIME.Domain -> UTCTime -> XMPP.Message -> ByteString
mkMessageID domain now message = ((s"<" ++) . (++ s">")) $
- MIME.renderAddressSpec $ flip MIME.AddrSpec domain
- (fromString $ time ++ "." ++ sid ++ "." ++ thread)
+ MIME.renderAddressSpec $ MIME.AddrSpec
+ (fromString $ time ++ "." ++ sid ++ "." ++ thread) domain
where
- sid = fromMaybe "=00" $ equalsEncode <$> XMPP.stanzaID message
+ sid = maybe "=00" equalsEncode $ XMPP.stanzaID message
thread =
- fromMaybe "=00" $
- fmap (equalsEncode . mconcat . XML.elementText) $
+ maybe "=00" (equalsEncode . mconcat . XML.elementText) $
child (s"{jabber:component:accept}thread") message
time = formatTime defaultTimeLocale "%s" now