Skip to content

Commit

Permalink
Re-format
Browse files Browse the repository at this point in the history
  • Loading branch information
drewolson committed Jul 6, 2023
1 parent 71d5800 commit d8f69e2
Show file tree
Hide file tree
Showing 4 changed files with 14 additions and 14 deletions.
4 changes: 2 additions & 2 deletions src/Bridge/Data/Unknown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,10 +13,10 @@ import Data.List (intercalate, nub, (\\))
class Unknown a where
isUnknown :: a -> Bool

areAllKnown :: Unknown a => [a] -> Bool
areAllKnown :: (Unknown a) => [a] -> Bool
areAllKnown = not . any isUnknown

knowns :: Unknown a => [a] -> [a]
knowns :: (Unknown a) => [a] -> [a]
knowns = filter (not . isUnknown)

hasUniqueEntries :: (Eq a, Unknown a) => [a] -> Bool
Expand Down
2 changes: 1 addition & 1 deletion src/Bridge/Slack/Json.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ instance
where
parseJSON = fmap PrefixedSnakeCaseJson . genericParseJSON (snakeCaseOptions $ typeNameSize @a)

typeNameSize :: forall a. Typeable (a :: Type) => Int
typeNameSize :: forall a. (Typeable (a :: Type)) => Int
typeNameSize = length $ show $ (typeOf @a) undefined

snakeCaseOptions :: Int -> Options
Expand Down
20 changes: 10 additions & 10 deletions src/Bridge/Slack/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Network.WebSockets qualified as WS
import System.Environment (getEnv)
import Wuss qualified

slackRequest :: MonadIO m => String -> String -> RequestHeaders -> m Request
slackRequest :: (MonadIO m) => String -> String -> RequestHeaders -> m Request
slackRequest token url headers = do
initReq <- liftIO $ parseRequest url

Expand All @@ -38,7 +38,7 @@ slackRequest token url headers = do
requestHeaders = [("Authorization", "Bearer " <> BS.pack token)] <> headers
}

getConnectionData :: MonadIO m => String -> m ConnectionData
getConnectionData :: (MonadIO m) => String -> m ConnectionData
getConnectionData token = do
req <-
slackRequest
Expand All @@ -48,14 +48,14 @@ getConnectionData token = do

getResponseBody <$> httpJSON req

fetchConnectionInfo :: MonadIO m => String -> m (String, PortNumber, String)
fetchConnectionInfo :: (MonadIO m) => String -> m (String, PortNumber, String)
fetchConnectionInfo token = do
ConnectionData {connectionDataUrl} <- getConnectionData token
let url = fromMaybe connectionDataUrl (T.stripPrefix "wss://" connectionDataUrl)
let (host, path) = T.breakOn "/" url
pure (T.unpack host, 443, T.unpack path)

postMessage :: MonadIO m => String -> PostMessage -> m ()
postMessage :: (MonadIO m) => String -> PostMessage -> m ()
postMessage token message = do
initReq <-
slackRequest
Expand All @@ -65,23 +65,23 @@ postMessage token message = do

void $ httpLBS $ initReq {requestBody = RequestBodyLBS $ encode message}

ack :: MonadIO m => WS.Connection -> Event -> m ()
ack :: (MonadIO m) => WS.Connection -> Event -> m ()
ack conn = liftIO . WS.sendTextData conn . encode . ackFromEvent

sendJson :: (ToJSON a, MonadIO m) => WS.Connection -> a -> m ()
sendJson conn = liftIO . WS.sendTextData conn . encode

sendClose :: MonadIO m => WS.Connection -> m ()
sendClose :: (MonadIO m) => WS.Connection -> m ()
sendClose conn = liftIO $ WS.sendClose conn ("close" :: Text)

receive :: (WS.WebSocketsData a, MonadIO m) => WS.Connection -> m a
receive = liftIO . WS.receiveData

handleHelpCommand :: MonadIO m => WS.Connection -> Event -> m ()
handleHelpCommand :: (MonadIO m) => WS.Connection -> Event -> m ()
handleHelpCommand conn event =
sendJson conn $ errorAck event $ Formatter.codeBlock Help.helpText

handleBridgeCommand :: MonadIO m => String -> WS.Connection -> Event -> SlashCommand -> m ()
handleBridgeCommand :: (MonadIO m) => String -> WS.Connection -> Event -> SlashCommand -> m ()
handleBridgeCommand token conn event slashCommand@SlashCommand {slashCommandText} = do
case Parser.parse $ T.strip slashCommandText of
Left err -> do
Expand All @@ -92,10 +92,10 @@ handleBridgeCommand token conn event slashCommand@SlashCommand {slashCommandText
let responseText = Formatter.codeBlock $ Formatter.format diagram
postMessage token $ postMessageFromSlashCommand responseText slashCommand

loop :: Monad m => MaybeT m a -> m ()
loop :: (Monad m) => MaybeT m a -> m ()
loop = void . runMaybeT . forever

quit :: MonadPlus m => m ()
quit :: (MonadPlus m) => m ()
quit = mzero

handler :: String -> WS.ClientApp ()
Expand Down
2 changes: 1 addition & 1 deletion src/Bridge/Text/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ import Text.Megaparsec.Char (char, space, space1, string, string')

type Parser = Parsec Void Text

rightOrFail :: MonadFail m => Either String a -> m a
rightOrFail :: (MonadFail m) => Either String a -> m a
rightOrFail = either fail pure

parseRank :: Parser Rank
Expand Down

0 comments on commit d8f69e2

Please sign in to comment.