{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-overlapping-patterns #-}
module Lambdabot.Config.Core
( commandPrefixes
, disabledCommands
, editDistanceLimit
, enableInsults
, onStartupCmds
, outputDir
, dataDir
, lbVersion
, textWidth
, uncaughtExceptionHandler
, replaceRootLogger
, lbRootLoggerPath
, consoleLogHandle
, consoleLogLevel
, consoleLogFormat
) where
import Lambdabot.Config
import Lambdabot.Logging
import Control.Exception
import System.IO
import Data.Version
config "commandPrefixes" [t| [String] |] [| ["@", "?"] |]
config "disabledCommands" [t| [String] |] [| [] |]
config "editDistanceLimit" [t| Int |] [| 3 :: Int |]
config "enableInsults" [t| Bool |] [| True |]
configWithMerge [| (++) |] "onStartupCmds" [t| [String] |] [| ["offline"] |]
config "outputDir" [t| FilePath |] [| "State/" |]
config "dataDir" [t| FilePath |] [| "." |]
config "lbVersion" [t| Version |] [| Version [] [] |]
config "textWidth" [t| Int |] [| 200 :: Int |]
config "replaceRootLogger" [t| Bool |] [| True |]
config "lbRootLoggerPath" [t| [String] |] [| [] |]
config "consoleLogHandle" [t| Handle |] [| stderr |]
config "consoleLogLevel" [t| Priority |] [| NOTICE |]
config "consoleLogFormat" [t| String |] [| "[$prio] $loggername: $msg" |]
defaultIrcHandler :: SomeException -> IO ()
defaultIrcHandler = errorM . ("Main: caught (and ignoring) "++) . show
config "uncaughtExceptionHandler" [t| SomeException -> IO () |] [| defaultIrcHandler |]