{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -fno-warn-overlapping-patterns #-} module Lambdabot.Plugin.Misc.Error (errorPlugin, failOnLoad, errorOnLoad) where import Lambdabot.Config import Lambdabot.Plugin import Control.Monad config "failOnLoad" [t| Bool |] [| False |] config "errorOnLoad" [t| Bool |] [| False |] errorPlugin :: Module () errorPlugin :: Module () errorPlugin = Module () forall st. Module st newModule { moduleCmds :: ModuleT () LB [Command (ModuleT () LB)] moduleCmds = [Command (ModuleT () LB)] -> ModuleT () LB [Command (ModuleT () LB)] forall (m :: * -> *) a. Monad m => a -> m a return [ (String -> Command Identity command String "error") { help :: Cmd (ModuleT () LB) () help = String -> Cmd (ModuleT () LB) () forall (m :: * -> *). Monad m => String -> Cmd m () say String "Throw an error, see what lambdabot does with it!" , process :: String -> Cmd (ModuleT () LB) () process = String -> Cmd (ModuleT () LB) () forall a. HasCallStack => String -> a error (String -> Cmd (ModuleT () LB) ()) -> (String -> String) -> String -> Cmd (ModuleT () LB) () forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> String forall a. Show a => a -> String show } , (String -> Command Identity command String "fail") { help :: Cmd (ModuleT () LB) () help = String -> Cmd (ModuleT () LB) () forall (m :: * -> *). Monad m => String -> Cmd m () say String "Throw an error, see what lambdabot does with it!" , process :: String -> Cmd (ModuleT () LB) () process = String -> Cmd (ModuleT () LB) () forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Cmd (ModuleT () LB) ()) -> (String -> String) -> String -> Cmd (ModuleT () LB) () forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> String forall a. Show a => a -> String show } ] , moduleInit :: ModuleT () LB () moduleInit = do Bool shouldFail <- Config Bool -> ModuleT () LB Bool forall (m :: * -> *) a. MonadConfig m => Config a -> m a getConfig Config Bool failOnLoad Bool -> ModuleT () LB () -> ModuleT () LB () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when Bool shouldFail (String -> ModuleT () LB () forall (m :: * -> *) a. MonadFail m => String -> m a fail String "Error module hates the world!") Bool shouldError <- Config Bool -> ModuleT () LB Bool forall (m :: * -> *) a. MonadConfig m => Config a -> m a getConfig Config Bool errorOnLoad Bool -> ModuleT () LB () -> ModuleT () LB () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when Bool shouldError (String -> ModuleT () LB () forall a. HasCallStack => String -> a error String "Error module hates the world!") }