@@ 2,36 2,20 @@ module Util where
import Prelude ()
import BasicPrelude
-import Control.Concurrent.STM (STM, atomically)
import Control.Applicative (many)
import Control.Concurrent
(ThreadId, forkFinally, myThreadId, throwTo)
import Data.Digest.Pure.SHA (sha1, bytestringDigest)
-import Data.Void (absurd)
-import Control.Error (exceptT)
-import Data.Time.Clock (UTCTime)
-import Data.Time.Format (parseTimeM, defaultTimeLocale)
import qualified Control.Exception as Ex
import qualified Data.Attoparsec.Text as Atto
import qualified Data.Text as Text
import qualified Data.XML.Types as XML
import qualified Network.Protocol.XMPP as XMPP
-import UnexceptionalIO.Trans (Unexceptional (lift))
-import qualified UnexceptionalIO.Trans as UIO
import qualified Data.ByteString.Lazy as LZ
-instance Unexceptional XMPP.XMPP where
- lift = liftIO . UIO.run
-
s :: (IsString s) => String -> s
s = fromString
-fromIO_ :: (Unexceptional m) => IO a -> m a
-fromIO_ = exceptT absurd return . UIO.fromIO' (error . show)
-
-atomicUIO :: (Unexceptional m) => STM a -> m a
-atomicUIO = fromIO_ . atomically
-
escapeJid :: Text -> Text
escapeJid txt = mconcat result
where
@@ 156,10 140,6 @@ bareTxt (XMPP.JID (Just node) domain _) =
mconcat [XMPP.strNode node, s"@", XMPP.strDomain domain]
bareTxt (XMPP.JID Nothing domain _) = XMPP.strDomain domain
-parseXMPPTime :: Text -> Maybe UTCTime
-parseXMPPTime =
- parseTimeM False defaultTimeLocale "%Y-%m-%dT%H:%M:%S%QZ" . textToString
-
mkElement :: XML.Name -> Text -> XML.Element
mkElement name content = XML.Element name []
[XML.NodeContent $ XML.ContentText content]
@@ 21,26 21,16 @@ common defs
containers >=0.5 && <0.6,
clock >=0.7 && <0.8,
errors >=2.3 && <2.4,
- focus >= 1.0.1 && < 1.1,
hedis,
HTTP,
http-types,
- lens >=4.16 && <4.18,
- mime-mail >=0.4 && < 0.5,
monad-loops,
network >= 2.6.3 && < 2.7,
network-protocol-xmpp >=0.4 && <0.5,
network-uri >=2.6 && <2.7,
- purebred-email >=0.4.1 && <0.5,
safe,
SHA,
- stm >=2.4 && <2.6,
- stm-containers >= 1.1.0 && < 1.2,
- stm-delay >=0.1 && <0.2,
text >=1.2 && <1.3,
- time >=1.5 && <2.0,
- unexceptionalio-trans >=0.5 && <0.6,
- uuid >= 1.3.13 && < 1.4,
xml-types >=0.3 && <0.4
executable gateway