-- Copyright (c) 2005-6 Don Stewart - http://www.cse.unsw.edu.au/~dons
-- GPL version 2 or later (see http://www.gnu.org/copyleft/gpl.html)

-- | Lambdabot version information
module Lambdabot.Plugin.Core.Version (versionPlugin) where

import Lambdabot.Plugin
import Data.Version (showVersion)

versionPlugin :: Module ()
versionPlugin :: Module ()
versionPlugin = forall st. Module st
newModule
    { moduleCmds :: ModuleT () LB [Command (ModuleT () LB)]
moduleCmds = forall (m :: * -> *) a. Monad m => a -> m a
return
        [ (String -> Command Identity
command String
"version")
            { help :: Cmd (ModuleT () LB) ()
help = forall (m :: * -> *). Monad m => String -> Cmd m ()
say forall a b. (a -> b) -> a -> b
$
                String
"version/source. Report the version " forall a. [a] -> [a] -> [a]
++
                String
"and git repo of this bot"
            , process :: String -> Cmd (ModuleT () LB) ()
process = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ do
                Version
ver <- forall (m :: * -> *) a. MonadConfig m => Config a -> m a
getConfig Config Version
lbVersion
                forall (m :: * -> *). Monad m => String -> Cmd m ()
say forall a b. (a -> b) -> a -> b
$ String
"lambdabot " forall a. [a] -> [a] -> [a]
++ Version -> String
showVersion Version
ver
                forall (m :: * -> *). Monad m => String -> Cmd m ()
say String
"git clone https://github.com/lambdabot/lambdabot"
            }
        ]
    }