-- | Commands and stuff
module Calamity.Commands.Command
    ( Command(..) ) where

import           Calamity.Commands.Check
import           Calamity.Commands.Context
import           Calamity.Commands.Error
import           Calamity.Commands.Group

import           Control.Lens              hiding ( (<.>), Context )

import           Data.List.NonEmpty        ( NonEmpty )
import           Data.Text                 as S
import           Data.Text.Lazy            as L

import           GHC.Generics

import           TextShow
import qualified TextShow.Generic          as TSG
import qualified Data.List.NonEmpty as NE

-- | A command
data Command = forall a. Command
  { Command -> NonEmpty Text
names    :: NonEmpty S.Text
  , Command -> Maybe Group
parent   :: Maybe Group
  , Command -> [Check]
checks   :: [Check] -- TODO check checks on default help
    -- ^ A list of checks that must pass for this command to be invoked
  , Command -> [Text]
params   :: [S.Text]
    -- ^ A list of the parameters the command takes, only used for constructing
    -- help messages.
  , Command -> Context -> Text
help     :: Context -> L.Text
    -- ^ A function producing the \'help\' for the command.
  , ()
parser   :: Context -> IO (Either CommandError a)
    -- ^ A function that parses the context for the command, producing the input
    -- @a@ for the command.
  , ()
callback :: (Context, a) -> IO (Maybe L.Text)
    -- ^ A function that given the context and the input (@a@) of the command,
    -- performs the action of the command.
  }

data CommandS = CommandS
  { CommandS -> NonEmpty Text
names  :: NonEmpty S.Text
  , CommandS -> [Text]
params :: [S.Text]
  , CommandS -> Maybe Text
parent :: Maybe S.Text
  , CommandS -> [Text]
checks :: [S.Text]
  }
  deriving ( (forall x. CommandS -> Rep CommandS x)
-> (forall x. Rep CommandS x -> CommandS) -> Generic CommandS
forall x. Rep CommandS x -> CommandS
forall x. CommandS -> Rep CommandS x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommandS x -> CommandS
$cfrom :: forall x. CommandS -> Rep CommandS x
Generic, Int -> CommandS -> ShowS
[CommandS] -> ShowS
CommandS -> String
(Int -> CommandS -> ShowS)
-> (CommandS -> String) -> ([CommandS] -> ShowS) -> Show CommandS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandS] -> ShowS
$cshowList :: [CommandS] -> ShowS
show :: CommandS -> String
$cshow :: CommandS -> String
showsPrec :: Int -> CommandS -> ShowS
$cshowsPrec :: Int -> CommandS -> ShowS
Show )
  deriving ( Int -> CommandS -> Builder
Int -> CommandS -> Text
Int -> CommandS -> Text
[CommandS] -> Builder
[CommandS] -> Text
[CommandS] -> Text
CommandS -> Builder
CommandS -> Text
CommandS -> Text
(Int -> CommandS -> Builder)
-> (CommandS -> Builder)
-> ([CommandS] -> Builder)
-> (Int -> CommandS -> Text)
-> (CommandS -> Text)
-> ([CommandS] -> Text)
-> (Int -> CommandS -> Text)
-> (CommandS -> Text)
-> ([CommandS] -> Text)
-> TextShow CommandS
forall a.
(Int -> a -> Builder)
-> (a -> Builder)
-> ([a] -> Builder)
-> (Int -> a -> Text)
-> (a -> Text)
-> ([a] -> Text)
-> (Int -> a -> Text)
-> (a -> Text)
-> ([a] -> Text)
-> TextShow a
showtlList :: [CommandS] -> Text
$cshowtlList :: [CommandS] -> Text
showtl :: CommandS -> Text
$cshowtl :: CommandS -> Text
showtlPrec :: Int -> CommandS -> Text
$cshowtlPrec :: Int -> CommandS -> Text
showtList :: [CommandS] -> Text
$cshowtList :: [CommandS] -> Text
showt :: CommandS -> Text
$cshowt :: CommandS -> Text
showtPrec :: Int -> CommandS -> Text
$cshowtPrec :: Int -> CommandS -> Text
showbList :: [CommandS] -> Builder
$cshowbList :: [CommandS] -> Builder
showb :: CommandS -> Builder
$cshowb :: CommandS -> Builder
showbPrec :: Int -> CommandS -> Builder
$cshowbPrec :: Int -> CommandS -> Builder
TextShow ) via TSG.FromGeneric CommandS

instance Show Command where
  showsPrec :: Int -> Command -> ShowS
showsPrec d :: Int
d Command { NonEmpty Text
names :: NonEmpty Text
$sel:names:Command :: Command -> NonEmpty Text
names, [Text]
params :: [Text]
$sel:params:Command :: Command -> [Text]
params, Maybe Group
parent :: Maybe Group
$sel:parent:Command :: Command -> Maybe Group
parent, [Check]
checks :: [Check]
$sel:checks:Command :: Command -> [Check]
checks } = Int -> CommandS -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (CommandS -> ShowS) -> CommandS -> ShowS
forall a b. (a -> b) -> a -> b
$ NonEmpty Text -> [Text] -> Maybe Text -> [Text] -> CommandS
CommandS NonEmpty Text
names [Text]
params (NonEmpty Text -> Text
forall a. NonEmpty a -> a
NE.head (NonEmpty Text -> Text) -> Maybe (NonEmpty Text) -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Group
parent Maybe Group
-> Getting (First (NonEmpty Text)) (Maybe Group) (NonEmpty Text)
-> Maybe (NonEmpty Text)
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Group -> Const (First (NonEmpty Text)) Group)
-> Maybe Group -> Const (First (NonEmpty Text)) (Maybe Group)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Group -> Const (First (NonEmpty Text)) Group)
 -> Maybe Group -> Const (First (NonEmpty Text)) (Maybe Group))
-> ((NonEmpty Text
     -> Const (First (NonEmpty Text)) (NonEmpty Text))
    -> Group -> Const (First (NonEmpty Text)) Group)
-> Getting (First (NonEmpty Text)) (Maybe Group) (NonEmpty Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IsLabel
  "names"
  ((NonEmpty Text -> Const (First (NonEmpty Text)) (NonEmpty Text))
   -> Group -> Const (First (NonEmpty Text)) Group)
(NonEmpty Text -> Const (First (NonEmpty Text)) (NonEmpty Text))
-> Group -> Const (First (NonEmpty Text)) Group
#names)
    ([Check]
checks [Check] -> Getting (Endo [Text]) [Check] Text -> [Text]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (Check -> Const (Endo [Text]) Check)
-> [Check] -> Const (Endo [Text]) [Check]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Check -> Const (Endo [Text]) Check)
 -> [Check] -> Const (Endo [Text]) [Check])
-> ((Text -> Const (Endo [Text]) Text)
    -> Check -> Const (Endo [Text]) Check)
-> Getting (Endo [Text]) [Check] Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IsLabel
  "name"
  ((Text -> Const (Endo [Text]) Text)
   -> Check -> Const (Endo [Text]) Check)
(Text -> Const (Endo [Text]) Text)
-> Check -> Const (Endo [Text]) Check
#name)

instance TextShow Command where
  showbPrec :: Int -> Command -> Builder
showbPrec d :: Int
d Command { NonEmpty Text
names :: NonEmpty Text
$sel:names:Command :: Command -> NonEmpty Text
names, [Text]
params :: [Text]
$sel:params:Command :: Command -> [Text]
params, Maybe Group
parent :: Maybe Group
$sel:parent:Command :: Command -> Maybe Group
parent, [Check]
checks :: [Check]
$sel:checks:Command :: Command -> [Check]
checks } = Int -> CommandS -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
d (CommandS -> Builder) -> CommandS -> Builder
forall a b. (a -> b) -> a -> b
$ NonEmpty Text -> [Text] -> Maybe Text -> [Text] -> CommandS
CommandS NonEmpty Text
names [Text]
params (NonEmpty Text -> Text
forall a. NonEmpty a -> a
NE.head (NonEmpty Text -> Text) -> Maybe (NonEmpty Text) -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Group
parent Maybe Group
-> Getting (First (NonEmpty Text)) (Maybe Group) (NonEmpty Text)
-> Maybe (NonEmpty Text)
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Group -> Const (First (NonEmpty Text)) Group)
-> Maybe Group -> Const (First (NonEmpty Text)) (Maybe Group)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Group -> Const (First (NonEmpty Text)) Group)
 -> Maybe Group -> Const (First (NonEmpty Text)) (Maybe Group))
-> ((NonEmpty Text
     -> Const (First (NonEmpty Text)) (NonEmpty Text))
    -> Group -> Const (First (NonEmpty Text)) Group)
-> Getting (First (NonEmpty Text)) (Maybe Group) (NonEmpty Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IsLabel
  "names"
  ((NonEmpty Text -> Const (First (NonEmpty Text)) (NonEmpty Text))
   -> Group -> Const (First (NonEmpty Text)) Group)
(NonEmpty Text -> Const (First (NonEmpty Text)) (NonEmpty Text))
-> Group -> Const (First (NonEmpty Text)) Group
#names)
    ([Check]
checks [Check] -> Getting (Endo [Text]) [Check] Text -> [Text]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (Check -> Const (Endo [Text]) Check)
-> [Check] -> Const (Endo [Text]) [Check]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Check -> Const (Endo [Text]) Check)
 -> [Check] -> Const (Endo [Text]) [Check])
-> ((Text -> Const (Endo [Text]) Text)
    -> Check -> Const (Endo [Text]) Check)
-> Getting (Endo [Text]) [Check] Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IsLabel
  "name"
  ((Text -> Const (Endo [Text]) Text)
   -> Check -> Const (Endo [Text]) Check)
(Text -> Const (Endo [Text]) Text)
-> Check -> Const (Endo [Text]) Check
#name)