{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
module Lambdabot.Plugin.Telegram.Bot where

import Control.Monad
import Control.Monad.State 
import Data.Char
import Data.Coerce
import Data.Maybe
import qualified Data.Text as Text
import Data.Text (Text)
import GHC.Generics
import Telegram.Bot.API
import Telegram.Bot.Simple
import Telegram.Bot.Simple.UpdateParser
import Text.Read (readMaybe)

import Lambdabot.Plugin.Telegram.Shared
import Lambdabot.Plugin.Telegram.Bot.Generic

-- | Telegram Model.
type Model = TelegramState

-- | Supported actions:
-- * send everything obtained from user to lambdabot ("proxy" command).
-- * send exact module command to lambdabot.
-- * send response back to user.
data Action = SendEverything Msg | SendModule ModuleCmd | SendBack Msg

-- | Supported modules.
data ModuleCmd
  = EvalModule EvalCmd
  | CheckModule CheckCmd
  | DjinnModule DjinnCmd
  | FreeModule FreeCmd
  | HaddockModule HaddockCmd
  | HoogleModule HoogleCmd
  | InstancesModule InstancesCmd
  | PlModule PlCmd
  | PointfulModule PointfulCmd
  | PrettyModule PrettyCmd
  | SystemModule SystemCmd
  | TypeModule TypeCmd
  | UndoModule UndoCmd
  | UnmtlModule UnmtlCmd
  | VersionModule VersionCmd
  | HelpModule HelpCmd
  | SourceModule SourceCmd

-- | Supported commands from @eval@ plugin.
data EvalCmd = Let Msg | Undefine Msg | Run Msg
  deriving ((forall x. EvalCmd -> Rep EvalCmd x)
-> (forall x. Rep EvalCmd x -> EvalCmd) -> Generic EvalCmd
forall x. Rep EvalCmd x -> EvalCmd
forall x. EvalCmd -> Rep EvalCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EvalCmd x -> EvalCmd
$cfrom :: forall x. EvalCmd -> Rep EvalCmd x
Generic, EvalCmd -> Text
EvalCmd -> Msg
(EvalCmd -> Msg) -> (EvalCmd -> Text) -> FromCommand EvalCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: EvalCmd -> Text
$cgetPrefix :: EvalCmd -> Text
getMessage :: EvalCmd -> Msg
$cgetMessage :: EvalCmd -> Msg
FromCommand)

-- | Supported commands from @check@ plugin.
data CheckCmd = Check Msg
  deriving ((forall x. CheckCmd -> Rep CheckCmd x)
-> (forall x. Rep CheckCmd x -> CheckCmd) -> Generic CheckCmd
forall x. Rep CheckCmd x -> CheckCmd
forall x. CheckCmd -> Rep CheckCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckCmd x -> CheckCmd
$cfrom :: forall x. CheckCmd -> Rep CheckCmd x
Generic, CheckCmd -> Text
CheckCmd -> Msg
(CheckCmd -> Msg) -> (CheckCmd -> Text) -> FromCommand CheckCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: CheckCmd -> Text
$cgetPrefix :: CheckCmd -> Text
getMessage :: CheckCmd -> Msg
$cgetMessage :: CheckCmd -> Msg
FromCommand)

-- | Supported commands from @djinn@ plugin.
data DjinnCmd = Djinn Msg | DjinnAdd Msg | DjinnDel Msg | DjinnEnv Msg | DjinnNames Msg | DjinnClr Msg | DjinnVer Msg
  deriving ((forall x. DjinnCmd -> Rep DjinnCmd x)
-> (forall x. Rep DjinnCmd x -> DjinnCmd) -> Generic DjinnCmd
forall x. Rep DjinnCmd x -> DjinnCmd
forall x. DjinnCmd -> Rep DjinnCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DjinnCmd x -> DjinnCmd
$cfrom :: forall x. DjinnCmd -> Rep DjinnCmd x
Generic, DjinnCmd -> Text
DjinnCmd -> Msg
(DjinnCmd -> Msg) -> (DjinnCmd -> Text) -> FromCommand DjinnCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: DjinnCmd -> Text
$cgetPrefix :: DjinnCmd -> Text
getMessage :: DjinnCmd -> Msg
$cgetMessage :: DjinnCmd -> Msg
FromCommand)

-- | Supported commands from @free@ plugin.
data FreeCmd = Free Msg
  deriving ((forall x. FreeCmd -> Rep FreeCmd x)
-> (forall x. Rep FreeCmd x -> FreeCmd) -> Generic FreeCmd
forall x. Rep FreeCmd x -> FreeCmd
forall x. FreeCmd -> Rep FreeCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FreeCmd x -> FreeCmd
$cfrom :: forall x. FreeCmd -> Rep FreeCmd x
Generic, FreeCmd -> Text
FreeCmd -> Msg
(FreeCmd -> Msg) -> (FreeCmd -> Text) -> FromCommand FreeCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: FreeCmd -> Text
$cgetPrefix :: FreeCmd -> Text
getMessage :: FreeCmd -> Msg
$cgetMessage :: FreeCmd -> Msg
FromCommand)

-- | Supported commands from @haddock@ plugin.
data HaddockCmd = Index Msg
  deriving ((forall x. HaddockCmd -> Rep HaddockCmd x)
-> (forall x. Rep HaddockCmd x -> HaddockCmd) -> Generic HaddockCmd
forall x. Rep HaddockCmd x -> HaddockCmd
forall x. HaddockCmd -> Rep HaddockCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HaddockCmd x -> HaddockCmd
$cfrom :: forall x. HaddockCmd -> Rep HaddockCmd x
Generic, HaddockCmd -> Text
HaddockCmd -> Msg
(HaddockCmd -> Msg)
-> (HaddockCmd -> Text) -> FromCommand HaddockCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: HaddockCmd -> Text
$cgetPrefix :: HaddockCmd -> Text
getMessage :: HaddockCmd -> Msg
$cgetMessage :: HaddockCmd -> Msg
FromCommand)

-- | Supported commands from @hoogle@ plugin.
data HoogleCmd = Hoogle Msg
  deriving ((forall x. HoogleCmd -> Rep HoogleCmd x)
-> (forall x. Rep HoogleCmd x -> HoogleCmd) -> Generic HoogleCmd
forall x. Rep HoogleCmd x -> HoogleCmd
forall x. HoogleCmd -> Rep HoogleCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HoogleCmd x -> HoogleCmd
$cfrom :: forall x. HoogleCmd -> Rep HoogleCmd x
Generic, HoogleCmd -> Text
HoogleCmd -> Msg
(HoogleCmd -> Msg) -> (HoogleCmd -> Text) -> FromCommand HoogleCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: HoogleCmd -> Text
$cgetPrefix :: HoogleCmd -> Text
getMessage :: HoogleCmd -> Msg
$cgetMessage :: HoogleCmd -> Msg
FromCommand)

-- | Supported commands from @instances@ plugin.
data InstancesCmd = Instances Msg | InstancesImporting Msg
  deriving ((forall x. InstancesCmd -> Rep InstancesCmd x)
-> (forall x. Rep InstancesCmd x -> InstancesCmd)
-> Generic InstancesCmd
forall x. Rep InstancesCmd x -> InstancesCmd
forall x. InstancesCmd -> Rep InstancesCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InstancesCmd x -> InstancesCmd
$cfrom :: forall x. InstancesCmd -> Rep InstancesCmd x
Generic, InstancesCmd -> Text
InstancesCmd -> Msg
(InstancesCmd -> Msg)
-> (InstancesCmd -> Text) -> FromCommand InstancesCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: InstancesCmd -> Text
$cgetPrefix :: InstancesCmd -> Text
getMessage :: InstancesCmd -> Msg
$cgetMessage :: InstancesCmd -> Msg
FromCommand)

-- | Supported commands from @pl@ plugin.
data PlCmd = Pl Msg | PlResume Msg
  deriving ((forall x. PlCmd -> Rep PlCmd x)
-> (forall x. Rep PlCmd x -> PlCmd) -> Generic PlCmd
forall x. Rep PlCmd x -> PlCmd
forall x. PlCmd -> Rep PlCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlCmd x -> PlCmd
$cfrom :: forall x. PlCmd -> Rep PlCmd x
Generic, PlCmd -> Text
PlCmd -> Msg
(PlCmd -> Msg) -> (PlCmd -> Text) -> FromCommand PlCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: PlCmd -> Text
$cgetPrefix :: PlCmd -> Text
getMessage :: PlCmd -> Msg
$cgetMessage :: PlCmd -> Msg
FromCommand)

-- | Supported commands from @pointful@ plugin.
data PointfulCmd = Pointful Msg | Pointy Msg | Repoint Msg | Unpointless Msg | Unpl Msg | Unpf Msg
  deriving ((forall x. PointfulCmd -> Rep PointfulCmd x)
-> (forall x. Rep PointfulCmd x -> PointfulCmd)
-> Generic PointfulCmd
forall x. Rep PointfulCmd x -> PointfulCmd
forall x. PointfulCmd -> Rep PointfulCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PointfulCmd x -> PointfulCmd
$cfrom :: forall x. PointfulCmd -> Rep PointfulCmd x
Generic, PointfulCmd -> Text
PointfulCmd -> Msg
(PointfulCmd -> Msg)
-> (PointfulCmd -> Text) -> FromCommand PointfulCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: PointfulCmd -> Text
$cgetPrefix :: PointfulCmd -> Text
getMessage :: PointfulCmd -> Msg
$cgetMessage :: PointfulCmd -> Msg
FromCommand)

-- | Supported commands from @pretty@ plugin.
data PrettyCmd = Pretty Msg
  deriving ((forall x. PrettyCmd -> Rep PrettyCmd x)
-> (forall x. Rep PrettyCmd x -> PrettyCmd) -> Generic PrettyCmd
forall x. Rep PrettyCmd x -> PrettyCmd
forall x. PrettyCmd -> Rep PrettyCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PrettyCmd x -> PrettyCmd
$cfrom :: forall x. PrettyCmd -> Rep PrettyCmd x
Generic, PrettyCmd -> Text
PrettyCmd -> Msg
(PrettyCmd -> Msg) -> (PrettyCmd -> Text) -> FromCommand PrettyCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: PrettyCmd -> Text
$cgetPrefix :: PrettyCmd -> Text
getMessage :: PrettyCmd -> Msg
$cgetMessage :: PrettyCmd -> Msg
FromCommand)

-- | Supported commands from @system@ plugin.
data SystemCmd = Listchans Msg | Listmodules Msg | Listservers Msg | List Msg | Echo Msg | Uptime Msg
  deriving ((forall x. SystemCmd -> Rep SystemCmd x)
-> (forall x. Rep SystemCmd x -> SystemCmd) -> Generic SystemCmd
forall x. Rep SystemCmd x -> SystemCmd
forall x. SystemCmd -> Rep SystemCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SystemCmd x -> SystemCmd
$cfrom :: forall x. SystemCmd -> Rep SystemCmd x
Generic, SystemCmd -> Text
SystemCmd -> Msg
(SystemCmd -> Msg) -> (SystemCmd -> Text) -> FromCommand SystemCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: SystemCmd -> Text
$cgetPrefix :: SystemCmd -> Text
getMessage :: SystemCmd -> Msg
$cgetMessage :: SystemCmd -> Msg
FromCommand)

-- | Supported commands from @type@ plugin.
data TypeCmd = Type Msg | Kind Msg
  deriving ((forall x. TypeCmd -> Rep TypeCmd x)
-> (forall x. Rep TypeCmd x -> TypeCmd) -> Generic TypeCmd
forall x. Rep TypeCmd x -> TypeCmd
forall x. TypeCmd -> Rep TypeCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TypeCmd x -> TypeCmd
$cfrom :: forall x. TypeCmd -> Rep TypeCmd x
Generic, TypeCmd -> Text
TypeCmd -> Msg
(TypeCmd -> Msg) -> (TypeCmd -> Text) -> FromCommand TypeCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: TypeCmd -> Text
$cgetPrefix :: TypeCmd -> Text
getMessage :: TypeCmd -> Msg
$cgetMessage :: TypeCmd -> Msg
FromCommand)

-- | Supported commands from @undo@ plugin.
data UndoCmd = Undo Msg | Do Msg
  deriving ((forall x. UndoCmd -> Rep UndoCmd x)
-> (forall x. Rep UndoCmd x -> UndoCmd) -> Generic UndoCmd
forall x. Rep UndoCmd x -> UndoCmd
forall x. UndoCmd -> Rep UndoCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UndoCmd x -> UndoCmd
$cfrom :: forall x. UndoCmd -> Rep UndoCmd x
Generic, UndoCmd -> Text
UndoCmd -> Msg
(UndoCmd -> Msg) -> (UndoCmd -> Text) -> FromCommand UndoCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: UndoCmd -> Text
$cgetPrefix :: UndoCmd -> Text
getMessage :: UndoCmd -> Msg
$cgetMessage :: UndoCmd -> Msg
FromCommand)

-- | Supported commands from @unmtl@ plugin.
data UnmtlCmd = Unmtl Msg
  deriving ((forall x. UnmtlCmd -> Rep UnmtlCmd x)
-> (forall x. Rep UnmtlCmd x -> UnmtlCmd) -> Generic UnmtlCmd
forall x. Rep UnmtlCmd x -> UnmtlCmd
forall x. UnmtlCmd -> Rep UnmtlCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnmtlCmd x -> UnmtlCmd
$cfrom :: forall x. UnmtlCmd -> Rep UnmtlCmd x
Generic, UnmtlCmd -> Text
UnmtlCmd -> Msg
(UnmtlCmd -> Msg) -> (UnmtlCmd -> Text) -> FromCommand UnmtlCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: UnmtlCmd -> Text
$cgetPrefix :: UnmtlCmd -> Text
getMessage :: UnmtlCmd -> Msg
$cgetMessage :: UnmtlCmd -> Msg
FromCommand)

-- | Supported commands from @version@ plugin.
data VersionCmd = Tgversion Msg
  deriving ((forall x. VersionCmd -> Rep VersionCmd x)
-> (forall x. Rep VersionCmd x -> VersionCmd) -> Generic VersionCmd
forall x. Rep VersionCmd x -> VersionCmd
forall x. VersionCmd -> Rep VersionCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VersionCmd x -> VersionCmd
$cfrom :: forall x. VersionCmd -> Rep VersionCmd x
Generic, VersionCmd -> Text
VersionCmd -> Msg
(VersionCmd -> Msg)
-> (VersionCmd -> Text) -> FromCommand VersionCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: VersionCmd -> Text
$cgetPrefix :: VersionCmd -> Text
getMessage :: VersionCmd -> Msg
$cgetMessage :: VersionCmd -> Msg
FromCommand)

-- | Supported commands from @help@ plugin.
data HelpCmd = Help Msg
  deriving ((forall x. HelpCmd -> Rep HelpCmd x)
-> (forall x. Rep HelpCmd x -> HelpCmd) -> Generic HelpCmd
forall x. Rep HelpCmd x -> HelpCmd
forall x. HelpCmd -> Rep HelpCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HelpCmd x -> HelpCmd
$cfrom :: forall x. HelpCmd -> Rep HelpCmd x
Generic, HelpCmd -> Text
HelpCmd -> Msg
(HelpCmd -> Msg) -> (HelpCmd -> Text) -> FromCommand HelpCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: HelpCmd -> Text
$cgetPrefix :: HelpCmd -> Text
getMessage :: HelpCmd -> Msg
$cgetMessage :: HelpCmd -> Msg
FromCommand)

-- | Supported commands from @source@ plugin.
data SourceCmd = Src Msg
  deriving ((forall x. SourceCmd -> Rep SourceCmd x)
-> (forall x. Rep SourceCmd x -> SourceCmd) -> Generic SourceCmd
forall x. Rep SourceCmd x -> SourceCmd
forall x. SourceCmd -> Rep SourceCmd x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SourceCmd x -> SourceCmd
$cfrom :: forall x. SourceCmd -> Rep SourceCmd x
Generic, SourceCmd -> Text
SourceCmd -> Msg
(SourceCmd -> Msg) -> (SourceCmd -> Text) -> FromCommand SourceCmd
forall command.
(command -> Msg) -> (command -> Text) -> FromCommand command
getPrefix :: SourceCmd -> Text
$cgetPrefix :: SourceCmd -> Text
getMessage :: SourceCmd -> Msg
$cgetMessage :: SourceCmd -> Msg
FromCommand)

-- | The bot.
telegramLambdaBot :: TelegramState -> BotApp Model Action
telegramLambdaBot :: TelegramState -> BotApp TelegramState Action
telegramLambdaBot TelegramState
tgstate = BotApp :: forall model action.
model
-> (Update -> model -> Maybe action)
-> (action -> model -> Eff action model)
-> [BotJob model action]
-> BotApp model action
BotApp
  { botInitialModel :: TelegramState
botInitialModel = TelegramState
tgstate
  , botAction :: Update -> TelegramState -> Maybe Action
botAction = (TelegramState -> Update -> Maybe Action)
-> Update -> TelegramState -> Maybe Action
forall a b c. (a -> b -> c) -> b -> a -> c
flip TelegramState -> Update -> Maybe Action
updateToAction
  , botHandler :: Action -> TelegramState -> Eff Action TelegramState
botHandler = Action -> TelegramState -> Eff Action TelegramState
handleAction
  , botJobs :: [BotJob TelegramState Action]
botJobs = []
  }

-- | How to handle updates from Telegram.
updateToAction :: Model -> Update -> Maybe Action
updateToAction :: TelegramState -> Update -> Maybe Action
updateToAction TelegramState{Int
TBQueue Msg
Text
tgBotName :: TelegramState -> Text
tgCurrent :: TelegramState -> Int
tgOutput :: TelegramState -> TBQueue Msg
tgInput :: TelegramState -> TBQueue Msg
tgBotName :: Text
tgCurrent :: Int
tgOutput :: TBQueue Msg
tgInput :: TBQueue Msg
..} Update
update
  -- proxy command
  | Text -> Update -> Bool
isCommand Text
"irc" Update
update = Msg -> Action
SendEverything (Msg -> Action) -> Maybe Msg -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update
  -- eval commands
  | Text -> Update -> Bool
isCommand Text
"let" Update
update = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (EvalCmd -> ModuleCmd
EvalModule (EvalCmd -> ModuleCmd) -> Maybe EvalCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> EvalCmd
Let (Msg -> EvalCmd) -> Maybe Msg -> Maybe EvalCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"run" Update
update = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (EvalCmd -> ModuleCmd
EvalModule (EvalCmd -> ModuleCmd) -> Maybe EvalCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> EvalCmd
Run (Msg -> EvalCmd) -> Maybe Msg -> Maybe EvalCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"define" Update
update = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (EvalCmd -> ModuleCmd
EvalModule (EvalCmd -> ModuleCmd) -> Maybe EvalCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> EvalCmd
Let (Msg -> EvalCmd) -> Maybe Msg -> Maybe EvalCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"undefine" Update
update = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (EvalCmd -> ModuleCmd
EvalModule (EvalCmd -> ModuleCmd) -> Maybe EvalCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> EvalCmd
Undefine (Msg -> EvalCmd) -> Maybe Msg -> Maybe EvalCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- check commands
  | Text -> Update -> Bool
isCommand Text
"check" Update
update = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CheckCmd -> ModuleCmd
CheckModule (CheckCmd -> ModuleCmd) -> Maybe CheckCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> CheckCmd
Check (Msg -> CheckCmd) -> Maybe Msg -> Maybe CheckCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- djinn commands
  | Text -> Update -> Bool
isCommand Text
"djinn" Update
update = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DjinnCmd -> ModuleCmd
DjinnModule (DjinnCmd -> ModuleCmd) -> Maybe DjinnCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> DjinnCmd
Djinn (Msg -> DjinnCmd) -> Maybe Msg -> Maybe DjinnCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"djinnadd" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DjinnCmd -> ModuleCmd
DjinnModule (DjinnCmd -> ModuleCmd) -> Maybe DjinnCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> DjinnCmd
DjinnAdd (Msg -> DjinnCmd) -> Maybe Msg -> Maybe DjinnCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"djinndel" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DjinnCmd -> ModuleCmd
DjinnModule (DjinnCmd -> ModuleCmd) -> Maybe DjinnCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> DjinnCmd
DjinnDel (Msg -> DjinnCmd) -> Maybe Msg -> Maybe DjinnCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"djinnenv" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DjinnCmd -> ModuleCmd
DjinnModule (DjinnCmd -> ModuleCmd) -> Maybe DjinnCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> DjinnCmd
DjinnEnv (Msg -> DjinnCmd) -> Maybe Msg -> Maybe DjinnCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"djinnnames" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DjinnCmd -> ModuleCmd
DjinnModule (DjinnCmd -> ModuleCmd) -> Maybe DjinnCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> DjinnCmd
DjinnNames (Msg -> DjinnCmd) -> Maybe Msg -> Maybe DjinnCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"djinnclr" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DjinnCmd -> ModuleCmd
DjinnModule (DjinnCmd -> ModuleCmd) -> Maybe DjinnCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> DjinnCmd
DjinnClr (Msg -> DjinnCmd) -> Maybe Msg -> Maybe DjinnCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"djinnver" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DjinnCmd -> ModuleCmd
DjinnModule (DjinnCmd -> ModuleCmd) -> Maybe DjinnCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> DjinnCmd
DjinnVer (Msg -> DjinnCmd) -> Maybe Msg -> Maybe DjinnCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- free commands
  | Text -> Update -> Bool
isCommand Text
"free" Update
update = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FreeCmd -> ModuleCmd
FreeModule (FreeCmd -> ModuleCmd) -> Maybe FreeCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> FreeCmd
Free (Msg -> FreeCmd) -> Maybe Msg -> Maybe FreeCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- haddock
  | Text -> Update -> Bool
isCommand Text
"index" Update
update = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (HaddockCmd -> ModuleCmd
HaddockModule (HaddockCmd -> ModuleCmd) -> Maybe HaddockCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> HaddockCmd
Index (Msg -> HaddockCmd) -> Maybe Msg -> Maybe HaddockCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- hoogle
  | Text -> Update -> Bool
isCommand Text
"hoogle" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (HoogleCmd -> ModuleCmd
HoogleModule (HoogleCmd -> ModuleCmd) -> Maybe HoogleCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> HoogleCmd
Hoogle (Msg -> HoogleCmd) -> Maybe Msg -> Maybe HoogleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- instances
  | Text -> Update -> Bool
isCommand Text
"instances" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (InstancesCmd -> ModuleCmd
InstancesModule (InstancesCmd -> ModuleCmd)
-> Maybe InstancesCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> InstancesCmd
Instances (Msg -> InstancesCmd) -> Maybe Msg -> Maybe InstancesCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"instancesimporting" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (InstancesCmd -> ModuleCmd
InstancesModule (InstancesCmd -> ModuleCmd)
-> Maybe InstancesCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> InstancesCmd
InstancesImporting (Msg -> InstancesCmd) -> Maybe Msg -> Maybe InstancesCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- pl
  | Text -> Update -> Bool
isCommand Text
"pl" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PlCmd -> ModuleCmd
PlModule (PlCmd -> ModuleCmd) -> Maybe PlCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PlCmd
Pl (Msg -> PlCmd) -> Maybe Msg -> Maybe PlCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"plresume" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PlCmd -> ModuleCmd
PlModule (PlCmd -> ModuleCmd) -> Maybe PlCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PlCmd
PlResume (Msg -> PlCmd) -> Maybe Msg -> Maybe PlCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- pointful
  | Text -> Update -> Bool
isCommand Text
"pointful" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PointfulCmd -> ModuleCmd
PointfulModule (PointfulCmd -> ModuleCmd) -> Maybe PointfulCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PointfulCmd
Pointful (Msg -> PointfulCmd) -> Maybe Msg -> Maybe PointfulCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"pointy" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PointfulCmd -> ModuleCmd
PointfulModule (PointfulCmd -> ModuleCmd) -> Maybe PointfulCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PointfulCmd
Pointy (Msg -> PointfulCmd) -> Maybe Msg -> Maybe PointfulCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"repoint" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PointfulCmd -> ModuleCmd
PointfulModule (PointfulCmd -> ModuleCmd) -> Maybe PointfulCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PointfulCmd
Repoint (Msg -> PointfulCmd) -> Maybe Msg -> Maybe PointfulCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"unpointless" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PointfulCmd -> ModuleCmd
PointfulModule (PointfulCmd -> ModuleCmd) -> Maybe PointfulCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PointfulCmd
Unpointless (Msg -> PointfulCmd) -> Maybe Msg -> Maybe PointfulCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"unpl" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PointfulCmd -> ModuleCmd
PointfulModule (PointfulCmd -> ModuleCmd) -> Maybe PointfulCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PointfulCmd
Unpl (Msg -> PointfulCmd) -> Maybe Msg -> Maybe PointfulCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"unpf" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PointfulCmd -> ModuleCmd
PointfulModule (PointfulCmd -> ModuleCmd) -> Maybe PointfulCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PointfulCmd
Unpf (Msg -> PointfulCmd) -> Maybe Msg -> Maybe PointfulCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- pretty
  | Text -> Update -> Bool
isCommand Text
"pretty" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PrettyCmd -> ModuleCmd
PrettyModule (PrettyCmd -> ModuleCmd) -> Maybe PrettyCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> PrettyCmd
Pretty (Msg -> PrettyCmd) -> Maybe Msg -> Maybe PrettyCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- system
  -- FIXME: decide about `listchans`, `listservers`
  | Text -> Update -> Bool
isCommand Text
"listmodules" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SystemCmd -> ModuleCmd
SystemModule (SystemCmd -> ModuleCmd) -> Maybe SystemCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> SystemCmd
Listmodules (Msg -> SystemCmd) -> Maybe Msg -> Maybe SystemCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"list" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SystemCmd -> ModuleCmd
SystemModule (SystemCmd -> ModuleCmd) -> Maybe SystemCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> SystemCmd
List (Msg -> SystemCmd) -> Maybe Msg -> Maybe SystemCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"echo" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SystemCmd -> ModuleCmd
SystemModule (SystemCmd -> ModuleCmd) -> Maybe SystemCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> SystemCmd
Echo (Msg -> SystemCmd) -> Maybe Msg -> Maybe SystemCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"uptime" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SystemCmd -> ModuleCmd
SystemModule (SystemCmd -> ModuleCmd) -> Maybe SystemCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> SystemCmd
Uptime (Msg -> SystemCmd) -> Maybe Msg -> Maybe SystemCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- type
  | Text -> Update -> Bool
isCommand Text
"type" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TypeCmd -> ModuleCmd
TypeModule (TypeCmd -> ModuleCmd) -> Maybe TypeCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> TypeCmd
Type (Msg -> TypeCmd) -> Maybe Msg -> Maybe TypeCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"kind" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TypeCmd -> ModuleCmd
TypeModule (TypeCmd -> ModuleCmd) -> Maybe TypeCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> TypeCmd
Kind (Msg -> TypeCmd) -> Maybe Msg -> Maybe TypeCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- undo
  | Text -> Update -> Bool
isCommand Text
"undo" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (UndoCmd -> ModuleCmd
UndoModule (UndoCmd -> ModuleCmd) -> Maybe UndoCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> UndoCmd
Undo (Msg -> UndoCmd) -> Maybe Msg -> Maybe UndoCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Text -> Update -> Bool
isCommand Text
"do" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (UndoCmd -> ModuleCmd
UndoModule (UndoCmd -> ModuleCmd) -> Maybe UndoCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> UndoCmd
Do (Msg -> UndoCmd) -> Maybe Msg -> Maybe UndoCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- unmtl
  | Text -> Update -> Bool
isCommand Text
"unmtl" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (UnmtlCmd -> ModuleCmd
UnmtlModule (UnmtlCmd -> ModuleCmd) -> Maybe UnmtlCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> UnmtlCmd
Unmtl (Msg -> UnmtlCmd) -> Maybe Msg -> Maybe UnmtlCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- version
  | Text -> Update -> Bool
isCommand Text
"version" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (VersionCmd -> ModuleCmd
VersionModule (VersionCmd -> ModuleCmd) -> Maybe VersionCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> VersionCmd
Tgversion (Msg -> VersionCmd) -> Maybe Msg -> Maybe VersionCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- help
  | Text -> Update -> Bool
isCommand Text
"help" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (HelpCmd -> ModuleCmd
HelpModule (HelpCmd -> ModuleCmd) -> Maybe HelpCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> HelpCmd
Help (Msg -> HelpCmd) -> Maybe Msg -> Maybe HelpCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  -- source
  | Text -> Update -> Bool
isCommand Text
"src" Update
update
  = ModuleCmd -> Action
SendModule (ModuleCmd -> Action) -> Maybe ModuleCmd -> Maybe Action
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SourceCmd -> ModuleCmd
SourceModule (SourceCmd -> ModuleCmd) -> Maybe SourceCmd -> Maybe ModuleCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Msg -> SourceCmd
Src (Msg -> SourceCmd) -> Maybe Msg -> Maybe SourceCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Update -> Maybe Msg
updateToMsg Update
update))
  | Bool
otherwise = Maybe Action
forall a. Maybe a
Nothing
  where
    isCommand :: Text -> Update -> Bool
isCommand Text
cmd = Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Text -> Bool) -> (Update -> Maybe Text) -> Update -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UpdateParser Text -> Update -> Maybe Text
forall a. UpdateParser a -> Update -> Maybe a
parseUpdate (Text -> Text -> UpdateParser Text
commandWithBotName Text
tgBotName Text
cmd)
    dropCommand :: Text -> Text
dropCommand = (Char -> Bool) -> Text -> Text
Text.dropWhile Char -> Bool
isSpace (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
Text.dropWhile (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace)
    intToText :: Coercible a Integer => a -> Text
    intToText :: a -> Text
intToText = String -> Text
Text.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show (Integer -> String) -> (a -> Integer) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coercible a Integer => a -> Integer
coerce @_ @Integer
    updateToMsg :: Update -> Maybe Msg
updateToMsg Update
upd =
      Text -> Text -> Text -> Msg
Msg (Text -> Text -> Text -> Msg)
-> Maybe Text -> Maybe (Text -> Text -> Msg)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((ChatId -> Text) -> Maybe ChatId -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ChatId -> Text
forall a. Coercible a Integer => a -> Text
intToText (Maybe ChatId -> Maybe Text)
-> (Update -> Maybe ChatId) -> Update -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Update -> Maybe ChatId
updateChatId) Update
upd
          Maybe (Text -> Text -> Msg) -> Maybe Text -> Maybe (Text -> Msg)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Message -> Text) -> Maybe Message -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (MessageId -> Text
forall a. Coercible a Integer => a -> Text
intToText (MessageId -> Text) -> (Message -> MessageId) -> Message -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Message -> MessageId
messageMessageId) (Maybe Message -> Maybe Text)
-> (Update -> Maybe Message) -> Update -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Update -> Maybe Message
extractUpdateMessage) Update
upd
          Maybe (Text -> Msg) -> Maybe Text -> Maybe Msg
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
dropCommand (Maybe Text -> Maybe Text)
-> (Update -> Maybe Text) -> Update -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Update -> Maybe Text
updateMessageText) Update
upd

-- | Extract 'Msg' from incoming command and send to Lambdabot.
handlePluginCommand :: FromCommand cmd => cmd -> Model -> Eff Action Model
handlePluginCommand :: cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand cmd
cmd TelegramState
model = TelegramState
model TelegramState -> BotM () -> Eff Action TelegramState
forall a action model.
GetAction a action =>
model -> BotM a -> Eff action model
<# do
  IO () -> BotM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> BotM ()) -> IO () -> BotM ()
forall a b. (a -> b) -> a -> b
$ Msg -> TelegramState -> IO ()
writeInput (cmd -> Msg
forall command. FromCommand command => command -> Msg
fromCommand cmd
cmd) TelegramState
model
  () -> BotM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | How to handle module 'Action'.
handleModuleAction :: ModuleCmd -> Model -> Eff Action Model
handleModuleAction :: ModuleCmd -> TelegramState -> Eff Action TelegramState
handleModuleAction (EvalModule EvalCmd
cmd) TelegramState
model = EvalCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand EvalCmd
cmd TelegramState
model 
handleModuleAction (CheckModule CheckCmd
cmd) TelegramState
model = CheckCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand CheckCmd
cmd TelegramState
model
handleModuleAction (DjinnModule DjinnCmd
cmd) TelegramState
model = DjinnCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand DjinnCmd
cmd TelegramState
model
handleModuleAction (FreeModule FreeCmd
cmd) TelegramState
model = FreeCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand FreeCmd
cmd TelegramState
model
handleModuleAction (HaddockModule HaddockCmd
cmd) TelegramState
model = HaddockCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand HaddockCmd
cmd TelegramState
model
handleModuleAction (HoogleModule HoogleCmd
cmd) TelegramState
model = HoogleCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand HoogleCmd
cmd TelegramState
model
handleModuleAction (InstancesModule InstancesCmd
cmd) TelegramState
model = InstancesCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand InstancesCmd
cmd TelegramState
model
handleModuleAction (PlModule PlCmd
cmd) TelegramState
model = PlCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand PlCmd
cmd TelegramState
model
handleModuleAction (PointfulModule PointfulCmd
cmd) TelegramState
model = PointfulCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand PointfulCmd
cmd TelegramState
model
handleModuleAction (PrettyModule PrettyCmd
cmd) TelegramState
model = PrettyCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand PrettyCmd
cmd TelegramState
model
handleModuleAction (SystemModule SystemCmd
cmd) TelegramState
model = SystemCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand SystemCmd
cmd TelegramState
model
handleModuleAction (TypeModule TypeCmd
cmd) TelegramState
model = TypeCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand TypeCmd
cmd TelegramState
model
handleModuleAction (UndoModule UndoCmd
cmd) TelegramState
model = UndoCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand UndoCmd
cmd TelegramState
model
handleModuleAction (UnmtlModule UnmtlCmd
cmd) TelegramState
model = UnmtlCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand UnmtlCmd
cmd TelegramState
model
handleModuleAction (VersionModule VersionCmd
cmd) TelegramState
model = VersionCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand VersionCmd
cmd TelegramState
model
handleModuleAction (HelpModule HelpCmd
cmd) TelegramState
model = case (Msg -> Text
msgMessage (Msg -> Text) -> Msg -> Text
forall a b. (a -> b) -> a -> b
$ HelpCmd -> Msg
forall command. FromCommand command => command -> Msg
getMessage HelpCmd
cmd) of
  Text
"" -> TelegramState
model TelegramState -> BotM Action -> Eff Action TelegramState
forall a action model.
GetAction a action =>
model -> BotM a -> Eff action model
<# do
    Action -> BotM Action
forall (f :: * -> *) a. Applicative f => a -> f a
pure
      (Action -> BotM Action) -> Action -> BotM Action
forall a b. (a -> b) -> a -> b
$ Msg -> Action
SendBack
      (Msg -> Action) -> Msg -> Action
forall a b. (a -> b) -> a -> b
$ Msg :: Text -> Text -> Text -> Msg
Msg { msgChatId :: Text
msgChatId = Msg -> Text
msgChatId (Msg -> Text) -> Msg -> Text
forall a b. (a -> b) -> a -> b
$ HelpCmd -> Msg
forall command. FromCommand command => command -> Msg
getMessage HelpCmd
cmd
            , msgMsgId :: Text
msgMsgId = Msg -> Text
msgMsgId (Msg -> Text) -> Msg -> Text
forall a b. (a -> b) -> a -> b
$ HelpCmd -> Msg
forall command. FromCommand command => command -> Msg
getMessage HelpCmd
cmd
            , msgMessage :: Text
msgMessage = Text
helpCmd
            }
  Text
_  -> HelpCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand HelpCmd
cmd TelegramState
model
handleModuleAction (SourceModule SourceCmd
cmd) TelegramState
model = SourceCmd -> TelegramState -> Eff Action TelegramState
forall cmd.
FromCommand cmd =>
cmd -> TelegramState -> Eff Action TelegramState
handlePluginCommand SourceCmd
cmd TelegramState
model

-- | How to handle 'Action'.
handleAction :: Action -> Model -> Eff Action Model
handleAction :: Action -> TelegramState -> Eff Action TelegramState
handleAction (SendEverything Msg
msg) TelegramState
model = TelegramState
model TelegramState -> BotM () -> Eff Action TelegramState
forall a action model.
GetAction a action =>
model -> BotM a -> Eff action model
<# do
  IO () -> BotM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> BotM ()) -> IO () -> BotM ()
forall a b. (a -> b) -> a -> b
$ Msg -> TelegramState -> IO ()
writeInput Msg
msg TelegramState
model
  () -> BotM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
handleAction (SendModule ModuleCmd
moduleCmd) TelegramState
model = ModuleCmd -> TelegramState -> Eff Action TelegramState
handleModuleAction ModuleCmd
moduleCmd TelegramState
model
handleAction (SendBack Msg
msg) TelegramState
model = TelegramState
model TelegramState -> BotM () -> Eff Action TelegramState
forall a action model.
GetAction a action =>
model -> BotM a -> Eff action model
<# do
  let Msg Text
chatIdText Text
msgIdText Text
response = Msg
msg
      parseChatId :: Text -> Maybe ChatId
parseChatId = (Integer -> ChatId) -> Maybe Integer -> Maybe ChatId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> ChatId
ChatId (Maybe Integer -> Maybe ChatId)
-> (Text -> Maybe Integer) -> Text -> Maybe ChatId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Integer
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe Integer)
-> (Text -> String) -> Text -> Maybe Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack
      parseMsgId :: Text -> Maybe MessageId
parseMsgId  = (Integer -> MessageId) -> Maybe Integer -> Maybe MessageId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> MessageId
MessageId (Maybe Integer -> Maybe MessageId)
-> (Text -> Maybe Integer) -> Text -> Maybe MessageId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Integer
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe Integer)
-> (Text -> String) -> Text -> Maybe Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack
      mchatId :: Maybe ChatId
mchatId = Text -> Maybe ChatId
parseChatId Text
chatIdText
      mreplyMessageId :: Maybe MessageId
mreplyMessageId = Text -> Maybe MessageId
parseMsgId Text
msgIdText
  case Maybe ChatId
mchatId of
    Maybe ChatId
Nothing -> () -> BotM ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    Just ChatId
tgchatId -> do
      let req :: SendMessageRequest
req = SendMessageRequest :: SomeChatId
-> Text
-> Maybe ParseMode
-> Maybe [MessageEntity]
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe MessageId
-> Maybe Bool
-> Maybe SomeReplyMarkup
-> SendMessageRequest
SendMessageRequest
            { sendMessageChatId :: SomeChatId
sendMessageChatId                = ChatId -> SomeChatId
SomeChatId ChatId
tgchatId
            , sendMessageText :: Text
sendMessageText                  = Text
"```\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
response Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n```\n"
            , sendMessageParseMode :: Maybe ParseMode
sendMessageParseMode             = ParseMode -> Maybe ParseMode
forall a. a -> Maybe a
Just ParseMode
MarkdownV2
            , sendMessageEntities :: Maybe [MessageEntity]
sendMessageEntities              = Maybe [MessageEntity]
forall a. Maybe a
Nothing
            , sendMessageDisableWebPagePreview :: Maybe Bool
sendMessageDisableWebPagePreview = Maybe Bool
forall a. Maybe a
Nothing
            , sendMessageDisableNotification :: Maybe Bool
sendMessageDisableNotification   = Maybe Bool
forall a. Maybe a
Nothing
            , sendMessageProtectContent :: Maybe Bool
sendMessageProtectContent        = Maybe Bool
forall a. Maybe a
Nothing
            , sendMessageReplyToMessageId :: Maybe MessageId
sendMessageReplyToMessageId      = Maybe MessageId
mreplyMessageId
            , sendMessageAllowSendingWithoutReply :: Maybe Bool
sendMessageAllowSendingWithoutReply = Maybe Bool
forall a. Maybe a
Nothing
            , sendMessageReplyMarkup :: Maybe SomeReplyMarkup
sendMessageReplyMarkup           = Maybe SomeReplyMarkup
forall a. Maybe a
Nothing
            }
      Response Message
_ <- ClientM (Response Message) -> BotM (Response Message)
forall a. ClientM a -> BotM a
liftClientM (SendMessageRequest -> ClientM (Response Message)
sendMessage SendMessageRequest
req)
      () -> BotM ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

-- | Run Telegram bot.
runTelegramBot :: Token -> TelegramState -> IO ()
runTelegramBot :: Token -> TelegramState -> IO ()
runTelegramBot Token
token TelegramState
tgstate = do
  ClientEnv
env <- Token -> IO ClientEnv
defaultTelegramClientEnv Token
token
  Action -> IO ()
botActionFun <- BotApp TelegramState Action -> ClientEnv -> IO (Action -> IO ())
forall model action.
BotApp model action -> ClientEnv -> IO (action -> IO ())
startBotAsync (TelegramState -> BotApp TelegramState Action
telegramLambdaBot TelegramState
tgstate) ClientEnv
env
  IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Msg
response <- TelegramState -> IO Msg
readOutput TelegramState
tgstate
    Action -> IO ()
botActionFun (Msg -> Action
SendBack Msg
response)

-- | Help command text.
helpCmd :: Text
helpCmd :: Text
helpCmd = Text
"Lambdabot for Telegram provides following plugins:\n\
\\n\
\telegram check djinn free haddock hoogle instances pl pointful pretty source system type undo unmtl\n\
\\n\
\telegram plugin has following commands:\n\
\\n\
\- /version - version/source. Report the version and git repo of this bot\n\
\- /run - run <expr>. You have Haskell, 3 seconds and no IO. Go nuts!\n\
\- /let - let <x> = <e>. Add a binding.\n\
\- /define - let <x> = <e>. Add a binding.\n\
\- /undefine - undefine. Reset evaluator local bindings.\n\
\\n\
\check plugin has following command:\n\
\\n\
\- /check - check <expr>. You have QuickCheck and 3 seconds. Prove something.\n\
\\n\
\djinn plugin has following commands:\n\
\\n\
\- /djinn - djinn <type>. Generates Haskell code from a type.\n\
\- /djinnadd - djinn-add <expr>. Define a new function type or type synonym.\n\
\- /djinndel - djinn-del <ident>. Remove a symbol from the environment.\n\
\- /djinnenv - Show the current djinn environment.\n\
\- /djinnnames - Show the current djinn environment, compactly.\n\
\- /djinnclr - Reset the djinn environment.\n\
\- /djinnver - Show current djinn version.\n\
\\n\
\free plugin has following command:\n\
\\n\
\- /free - free <ident>. Generate theorems for free.\n\
\\n\
\haddock plugin has following command:\n\
\\n\
\- /index - index <ident>. Returns the Haskell modules in which <ident> is defined.\n\
\\n\
\hoogle plugin has following command:\n\
\\n\
\- /hoogle - hoogle <expr>. Haskell API Search for either names, or types.\n\
\\n\
\instances plugin has following commands:\n\
\\n\
\- /instances - instances <typeclass>. Fetch the instances of a typeclass.\n\
\- /instancesimporting - instancesimporting [<module> [<module> [<module...]]] <typeclass>. Fetch the instances of a typeclass, importing specified modules first.\n\
\\n\
\pl plugin has following command:\n\
\\n\
\- /pl - pointless <expr>. Play with pointfree code.\n\
\\n\
\pointful plugin has following commands:\n\
\\n\
\- /pointy - pointful <expr>. Make code pointier.\n\
\- /repoint - pointful <expr>. Make code pointier.\n\
\- /unpointless - pointful <expr>. Make code pointier.\n\
\- /unpl - pointful <expr>. Make code pointier.\n\
\- /unpf - pointful <expr>. Make code pointier.\n\
\\n\
\pretty plugin has following commands:\n\
\\n\
\- /pretty - pretty <expr>. Display haskell code in a pretty-printed manner\n\
\\n\
\type plugin has following commands:\n\
\\n\
\- /type - type <expr>. Return the type of a value.\n\
\- /kind - kind <type>. Return the kind of a type.\n\
\\n\
\source plugin has following commands:\n\
\- /src - src <id>. Display the implementation of a standard function.\n\
\\n\
\undo plugin has following commands:\n\
\\n\
\- /undo - undo <expr>. Translate do notation to Monad operators.\n\
\- /do - do <expr>. Translate Monad operators to do notation.\n\
\\n\
\unmtl has following commands:\n\
\\n\
\- /unmtl - unroll mtl monads.\n\
\\n\
\Other commands:\n\
\- /help - shows this help.\n\
\- /version - version/source. Report the version and git repo of this bot\n\
\\n\
\All plugins are independent from each other, i.e. have their own state or use different programs under the hood."