Skip to content

Commit

Permalink
Add Telegram.Bot.Simple.Debug
Browse files Browse the repository at this point in the history
  • Loading branch information
fizruk committed Jun 3, 2018
1 parent bc7c5bb commit 7db84c5
Show file tree
Hide file tree
Showing 2 changed files with 89 additions and 0 deletions.
2 changes: 2 additions & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,8 @@ dependencies:
- base
- lifted-base
- aeson
- aeson-pretty
- bytestring
- hashable
- http-api-data
- http-client
Expand Down
87 changes: 87 additions & 0 deletions src/Telegram/Bot/Simple/Debug.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,87 @@
module Telegram.Bot.Simple.Debug where

import Control.Monad.Trans (liftIO)
import Control.Monad.Writer (tell)
import Data.Aeson (ToJSON)
import qualified Data.Aeson.Encode.Pretty as Aeson
import qualified Data.ByteString.Lazy.Char8 as BSL8
import Data.Monoid ((<>))
import Debug.Trace (trace)
import qualified Telegram.Bot.API as Telegram
import Telegram.Bot.Simple

-- * Trace 'Telegram.Update's

-- | Trace (debug print) every 'Telegram.Update' before parsing it.
traceTelegramUpdatesWith
:: (Telegram.Update -> String) -- ^ How to display an update.
-> BotApp model action
-> BotApp model action
traceTelegramUpdatesWith f botApp = botApp
{ botAction = \update -> botAction botApp (trace (f update) update)
}

-- | Trace (debug print) every update as pretty JSON value.
traceTelegramUpdatesJSON :: BotApp model action -> BotApp model action
traceTelegramUpdatesJSON = traceTelegramUpdatesWith prettyJSONString

-- | Trace (debug print) every update using 'Show' instance.
traceTelegramUpdatesShow :: BotApp model action -> BotApp model action
traceTelegramUpdatesShow = traceTelegramUpdatesWith show

-- * Trace bot actions

-- | Trace (debug print) every incoming and issued action.
traceBotActionsWith
:: (action -> String) -- ^ How to display an action.
-> BotApp model action
-> BotApp model action
traceBotActionsWith f botApp = botApp { botHandler = newBotHandler }
where
traceAction action = action <$ do
liftIO $ putStrLn ("Issued action: " <> f action)

newBotHandler action model = do
Eff (tell (map (>>= traceAction) actions))
pure newModel
where
(newModel, actions) = runEff $
botHandler botApp
(trace ("Incoming action: " <> f action) action)
model

-- | Trace (debug print) bot actions using 'Show' instance.
traceBotActionsShow
:: Show action => BotApp model action -> BotApp model action
traceBotActionsShow = traceBotActionsWith show

-- * Trace bot state model

-- | Trace (debug print) bot model.
traceBotModelWith
:: (model -> String) -- ^ How to display a model.
-> BotApp model action
-> BotApp model action
traceBotModelWith f botApp = botApp
{ botInitialModel = traceModel (botInitialModel botApp)
, botHandler = newHandler
}
where
traceModel = trace <$> f <*> id

newHandler action model = traceModel <$> botHandler botApp action model

-- | Trace (debug print) bot model using 'Show' instance.
traceBotModelShow
:: Show model => BotApp model action -> BotApp model action
traceBotModelShow = traceBotModelWith show

-- | Trace (debug print) bot model using 'Show' instance.
traceBotModelJSON
:: ToJSON model => BotApp model action -> BotApp model action
traceBotModelJSON = traceBotModelWith prettyJSONString

-- * Helpers

prettyJSONString :: ToJSON a => a -> String
prettyJSONString = BSL8.unpack . Aeson.encodePretty

0 comments on commit 7db84c5

Please sign in to comment.