Skip to content

Commit

Permalink
Small haddock and function name changes.
Browse files Browse the repository at this point in the history
  • Loading branch information
solomon-b committed Dec 19, 2022
1 parent 96ccc7f commit cd74428
Show file tree
Hide file tree
Showing 12 changed files with 35 additions and 34 deletions.
4 changes: 2 additions & 2 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@ helloBot = Bot $ \s msg ->
Lifting Bots Over more complex inputs and outputs
-------------------------------------------------
```Haskell
liftSimpleBot :: Functor m => Bot m s Text Text -> Bot m s (RoomID, Event) (RoomID, Event)
liftSimpleBot (Bot bot) = Bot $ \s (rid, i) ->
embedTextBot :: Functor m => Bot m s Text Text -> Bot m s (RoomID, Event) (RoomID, Event)
embedTextBot (Bot bot) = Bot $ \s (rid, i) ->
fmap (\(i', s') -> ((rid, mkMsg i'), s')) $ bot s (viewBody i)

viewBody :: Event -> T.Text
Expand Down
6 changes: 3 additions & 3 deletions chat-bots-contrib/src/Data/Chat/Bot/Calculator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Data.Chat.Bot (Bot)
import Data.Chat.Bot.Calculator.Language as Language
import Data.Chat.Serialization (TextSerializer)
import Data.Chat.Serialization qualified as S
import Data.Chat.Server.Matrix (RoomID, liftSimpleBot)
import Data.Chat.Server.Matrix (RoomID, embedTextBot)
import Data.Chat.Utils (type (\/))
import Data.Text (Text)
import Data.Text qualified as Text
Expand All @@ -34,10 +34,10 @@ calculatorBot :: Bot IO CalcState Statement (CalcError \/ CalcResp)
calculatorBot = ask >>= state . execCalculator

calculatorBot' :: Bot IO CalcState Text Text
calculatorBot' = S.simplifyBot calculatorBot calculatorSerializer
calculatorBot' = S.translateBot calculatorBot calculatorSerializer

calculatorMatrixBot :: Bot IO CalcState (RoomID, Event) (RoomID, Event)
calculatorMatrixBot = liftSimpleBot calculatorBot'
calculatorMatrixBot = embedTextBot calculatorBot'

--------------------------------------------------------------------------------

Expand Down
9 changes: 4 additions & 5 deletions chat-bots-contrib/src/Data/Chat/Bot/CoinFlip.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,9 @@ import Data.Attoparsec.Text
import Data.Chat.Bot
import Data.Chat.Serialization (TextSerializer)
import Data.Chat.Serialization qualified as S
import Data.Chat.Server.Matrix (RoomID, liftSimpleBot)
import Data.Chat.Server.Matrix (RoomID, embedTextBot)
import Data.Text (Text)
import Data.Text qualified as Text
import Network.Matrix.Client (Event)
import System.Random (randomIO)

Expand All @@ -25,7 +26,7 @@ coinFlipBot :: Bot IO () () Bool
coinFlipBot = randomIO

coinFlipMatrixBot :: Bot IO () (RoomID, Event) (RoomID, Event)
coinFlipMatrixBot = liftSimpleBot $ S.simplifyBot coinFlipBot coinFlipSerializer
coinFlipMatrixBot = embedTextBot $ S.translateBot coinFlipBot coinFlipSerializer

--------------------------------------------------------------------------------

Expand All @@ -36,6 +37,4 @@ parser :: Text -> Maybe ()
parser = either (const Nothing) Just . parseOnly ("flip a coin" *> pure ())

printer :: Bool -> Text
printer = \case
True -> "Coin Flip Result: True"
False -> "Coin Flip Result: False"
printer p = "Coin Flip Result: " <> Text.pack (show p)
4 changes: 2 additions & 2 deletions chat-bots-contrib/src/Data/Chat/Bot/GHCI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import Data.Attoparsec.Text as A
import Data.Chat.Bot
import Data.Chat.Serialization (TextSerializer)
import Data.Chat.Serialization qualified as S
import Data.Chat.Server.Matrix (Event, liftSimpleBot)
import Data.Chat.Server.Matrix (Event, embedTextBot)
import Data.Text (Text)
import Data.Text qualified as Text
import GHC.Conc (threadDelay)
Expand All @@ -42,7 +42,7 @@ ghciBot p = Bot $
pure (Text.pack o, s)

ghciMatrixBot :: Process Handle Handle () -> Bot IO () (RoomID, Event) (RoomID, Event)
ghciMatrixBot handle = liftSimpleBot $ S.simplifyBot (ghciBot handle) ghciSerializer
ghciMatrixBot handle = embedTextBot $ S.translateBot (ghciBot handle) ghciSerializer

--------------------------------------------------------------------------------

Expand Down
4 changes: 2 additions & 2 deletions chat-bots-contrib/src/Data/Chat/Bot/Hello.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,9 +28,9 @@ helloBot :: Monad m => Bot m s () Text
helloBot = Bot $ \s () -> pure ("Are you talking to me, punk?", s)

-- | We can then embed our bot in the Matrix API using
-- 'liftSimpleBot'.
-- 'embedTextBot'.
helloMatrixBot :: Monad m => Bot m () (RoomID, Event) (RoomID, Event)
helloMatrixBot = liftSimpleBot $ S.simplifyBot helloBot helloBotSerializer
helloMatrixBot = embedTextBot $ S.translateBot helloBot helloBotSerializer

--------------------------------------------------------------------------------

Expand Down
4 changes: 2 additions & 2 deletions chat-bots-contrib/src/Data/Chat/Bot/Jitsi.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import Data.Chat.Bot (Bot, liftEffect)
import Data.Chat.Bot.Jitsi.Dictionary (adjectives, adverbs, pluralNouns, verbs)
import Data.Chat.Serialization (TextSerializer)
import Data.Chat.Serialization qualified as S
import Data.Chat.Server.Matrix (Event, RoomID, liftSimpleBot)
import Data.Chat.Server.Matrix (Event, RoomID, embedTextBot)
import Data.Text (Text)
import Data.Vector qualified as V
import System.Random (randomRIO)
Expand All @@ -25,7 +25,7 @@ jitsiBot :: Bot IO () () Text
jitsiBot = liftEffect jitsiUrl

jitsiMatrixBot :: Bot IO () (RoomID, Event) (RoomID, Event)
jitsiMatrixBot = liftSimpleBot $ S.simplifyBot jitsiBot jitsiSerializer
jitsiMatrixBot = embedTextBot $ S.translateBot jitsiBot jitsiSerializer

--------------------------------------------------------------------------------

Expand Down
4 changes: 2 additions & 2 deletions chat-bots-contrib/src/Data/Chat/Bot/Magic8Ball.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import Data.Attoparsec.Text
import Data.Chat.Bot
import Data.Chat.Serialization (TextSerializer)
import Data.Chat.Serialization qualified as S
import Data.Chat.Server.Matrix (RoomID, liftSimpleBot)
import Data.Chat.Server.Matrix (RoomID, embedTextBot)
import Data.Text (Text)
import Network.Matrix.Client (Event)
import System.Random
Expand All @@ -26,7 +26,7 @@ magic8BallBot = do
randomRIO (1, 20)

magic8BallMatrixBot :: Bot IO () (RoomID, Event) (RoomID, Event)
magic8BallMatrixBot = liftSimpleBot $ S.simplifyBot magic8BallBot magic8BallSerializer
magic8BallMatrixBot = embedTextBot $ S.translateBot magic8BallBot magic8BallSerializer

--------------------------------------------------------------------------------

Expand Down
2 changes: 1 addition & 1 deletion chat-bots-contrib/src/Data/Chat/Bot/Updog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ updogBot = Bot $ \s -> \case
OPP -> toListT [("yo, you know me!", s), ("HAH GOTTEM", s)]

updogMatrixBot :: Monad m => Bot m () (RoomID, Event) (RoomID, Event)
updogMatrixBot = liftSimpleBot $ S.simplifyBot updogBot updogSerializer
updogMatrixBot = embedTextBot $ S.translateBot updogBot updogSerializer

--------------------------------------------------------------------------------

Expand Down
8 changes: 5 additions & 3 deletions chat-bots-contrib/src/Data/Chat/Server/Matrix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Data.Chat.Server.Matrix
MatrixBot,
matrix,
simplifyMatrixBot,
liftSimpleBot,
embedTextBot,
RoomID,
Event,
)
Expand Down Expand Up @@ -93,8 +93,10 @@ simplifyMatrixBot (Bot bot) = Bot $ \s i -> do
(responses, nextState) <- bot s (RoomID mempty, mkMsg i)
pure (viewBody $ snd responses, nextState)

liftSimpleBot :: Functor m => Bot m s Text Text -> MatrixBot m s
liftSimpleBot (Bot bot) = Bot $ \s (rid, i) ->
-- | Map the input and output of a @Bot m s Text Text@ to the Matrix
-- I/O types.
embedTextBot :: Functor m => Bot m s Text Text -> MatrixBot m s
embedTextBot (Bot bot) = Bot $ \s (rid, i) ->
fmap (\(i', s') -> ((rid, mkMsg i'), s')) $ bot s (viewBody i)

viewBody :: Event -> Text
Expand Down
6 changes: 3 additions & 3 deletions chat-bots-contrib/test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ main = hspec $ do
helloBotSpec :: Spec
helloBotSpec =
describe "Hello Bot" $ do
let bot = S.simplifyBot helloBot helloBotSerializer
let bot = S.translateBot helloBot helloBotSerializer
it "responds to precisely its trigger phrase" $ do
let scenario =
[mkScript|
Expand All @@ -46,7 +46,7 @@ helloBotSpec =
calculatorBotSpec :: Spec
calculatorBotSpec =
describe "Calculator Bot" $ do
let bot = S.simplifyBot calculatorBot calculatorSerializer
let bot = S.translateBot calculatorBot calculatorSerializer
it "performs arithmetic" $ do
let scenario =
[mkScript|
Expand Down Expand Up @@ -74,7 +74,7 @@ calculatorBotSpec =
sessionizedBotSpec :: Spec
sessionizedBotSpec =
describe "Sessionized Bot" $ do
let bot = S.simplifyBot (sessionize mempty calculatorBot) (sessionSerializer calculatorSerializer)
let bot = S.translateBot (sessionize mempty calculatorBot) (sessionSerializer calculatorSerializer)
it "can instantiate a session" $ do
let scenario =
[mkScript|
Expand Down
12 changes: 6 additions & 6 deletions chat-bots/src/Data/Chat/Serialization.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,12 +11,12 @@ import Data.These

--------------------------------------------------------------------------------

simplifyBot ::
translateBot ::
Monad m =>
Bot m s bi bo ->
Serializer so si bo bi ->
Bot m s so si
simplifyBot (Bot bot) (Serializer parser printer) = Bot $ \s i ->
translateBot (Bot bot) (Serializer parser printer) = Bot $ \s i ->
case parser i of
Nothing -> emptyListT
Just i' -> do
Expand All @@ -32,12 +32,12 @@ data Serializer so si bo bi = Serializer
-- | A 'Serializer' whose 'Server' I/O has been specialized to 'Text'.
type TextSerializer = Serializer Text Text

-- | P
-- | Modify a 'Serializer' to parse and print a prefix string.
prefix :: Text -> TextSerializer x y -> TextSerializer x y
prefix prefix Serializer {..} =
prefix txt Serializer {..} =
Serializer
{ parser = \so -> parser (prefix <> ": " <> so),
printer = \bo -> prefix <> ":" <> printer bo
{ parser = \so -> parser (txt <> ": " <> so),
printer = \bo -> txt <> ":" <> printer bo
}

infixr 6 /+\
Expand Down
6 changes: 3 additions & 3 deletions cofree-bot/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ import Data.Chat.Bot.Sessions
import Data.Chat.Bot.Updog (updogBot, updogSerializer)
import Data.Chat.Serialization qualified as S
import Data.Chat.Server (annihilate, loop)
import Data.Chat.Server.Matrix (liftSimpleBot, matrix)
import Data.Chat.Server.Matrix (embedTextBot, matrix)
import Data.Chat.Server.Repl (repl)
import Data.Foldable (fold)
import GHC.Conc (threadDelay)
Expand Down Expand Up @@ -70,7 +70,7 @@ serializer' =
S./+\ ghciSerializer
S./+\ sessionSerializer calculatorSerializer

bot process = S.simplifyBot (bot' process) serializer'
bot process = S.translateBot (bot' process) serializer'

--------------------------------------------------------------------------------

Expand All @@ -92,5 +92,5 @@ matrixMain session xdgCache = withProcessWait_ ghciConfig $ \process -> do
void $ threadDelay 1e6
void $ hGetOutput (getStdout process)
state <- readState xdgCache
fixedBot <- flip (fixBotPersistent xdgCache) (fold state) $ hoistBot liftIO $ liftSimpleBot $ bot process
fixedBot <- flip (fixBotPersistent xdgCache) (fold state) $ hoistBot liftIO $ embedTextBot $ bot process
unsafeCrashInIO $ loop $ annihilate (matrix session xdgCache) $ batch $ fixedBot

0 comments on commit cd74428

Please sign in to comment.