This commit is contained in:
2018-12-23 23:52:19 +02:00
parent 092bde3987
commit 2d1098c1cd
8 changed files with 20 additions and 19 deletions

View File

@ -1,9 +1,9 @@
{-# Language Safe #-}
{-# Language RankNTypes #-}
{-# Language GADTs #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Safe #-}
module Bot.Extension where
import Bot.DSL
import Bot.DSL
data Extension meta = Extension { act :: forall m. (meta ~ Meta m, MonadExtension m) => Request meta -> m (Maybe (Response meta))
, name :: String }

View File

@ -1,7 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeFamilies #-}
module Bot.Lib where
@ -9,10 +8,9 @@ import Bot.DSL
import Bot.Extension
import Bot.Log
import Control.Monad (forever)
import Control.Monad.Catch (MonadCatch, SomeException, catch, try)
import Control.Monad.Catch (MonadCatch, SomeException, catch)
import Data.Maybe (catMaybes)
import qualified Data.Text as T
import GHC.Stack
tshow :: Show a => a -> T.Text
tshow = T.pack . show
@ -25,5 +23,5 @@ mainLoop extensions = forever $ catch go handleFail
go :: m ()
go = do
msg <- recvMsg
responses <- catMaybes <$> mapM (\ext -> (act ext) msg) extensions
responses <- catMaybes <$> mapM (`act` msg) extensions
mapM_ putMsg responses