module Calamity.Commands.Group
( Group(..) ) where
import Calamity.Commands.AliasType
import Calamity.Commands.Check
import {-# SOURCE #-} Calamity.Commands.Command
import {-# SOURCE #-} Calamity.Commands.Context
import Control.Lens hiding ( (<.>), Context )
import qualified Data.HashMap.Lazy as LH
import qualified Data.Text as S
import qualified Data.Text.Lazy as L
import GHC.Generics
import TextShow
import qualified TextShow.Generic as TSG
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NE
data Group = Group
{ Group -> NonEmpty Text
names :: NonEmpty S.Text
, Group -> Maybe Group
parent :: Maybe Group
, Group -> HashMap Text (Command, AliasType)
commands :: LH.HashMap S.Text (Command, AliasType)
, Group -> HashMap Text (Group, AliasType)
children :: LH.HashMap S.Text (Group, AliasType)
, Group -> Context -> Text
help :: Context -> L.Text
, Group -> [Check]
checks :: [Check]
}
deriving ( (forall x. Group -> Rep Group x)
-> (forall x. Rep Group x -> Group) -> Generic Group
forall x. Rep Group x -> Group
forall x. Group -> Rep Group x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Group x -> Group
$cfrom :: forall x. Group -> Rep Group x
Generic )
data GroupS = GroupS
{ GroupS -> NonEmpty Text
names :: NonEmpty S.Text
, GroupS -> Maybe Text
parent :: Maybe S.Text
, GroupS -> HashMap Text (Command, AliasType)
commands :: LH.HashMap S.Text (Command, AliasType)
, GroupS -> HashMap Text (Group, AliasType)
children :: LH.HashMap S.Text (Group, AliasType)
}
deriving ( (forall x. GroupS -> Rep GroupS x)
-> (forall x. Rep GroupS x -> GroupS) -> Generic GroupS
forall x. Rep GroupS x -> GroupS
forall x. GroupS -> Rep GroupS x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GroupS x -> GroupS
$cfrom :: forall x. GroupS -> Rep GroupS x
Generic, Int -> GroupS -> ShowS
[GroupS] -> ShowS
GroupS -> String
(Int -> GroupS -> ShowS)
-> (GroupS -> String) -> ([GroupS] -> ShowS) -> Show GroupS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GroupS] -> ShowS
$cshowList :: [GroupS] -> ShowS
show :: GroupS -> String
$cshow :: GroupS -> String
showsPrec :: Int -> GroupS -> ShowS
$cshowsPrec :: Int -> GroupS -> ShowS
Show )
deriving ( Int -> GroupS -> Builder
Int -> GroupS -> Text
Int -> GroupS -> Text
[GroupS] -> Builder
[GroupS] -> Text
[GroupS] -> Text
GroupS -> Builder
GroupS -> Text
GroupS -> Text
(Int -> GroupS -> Builder)
-> (GroupS -> Builder)
-> ([GroupS] -> Builder)
-> (Int -> GroupS -> Text)
-> (GroupS -> Text)
-> ([GroupS] -> Text)
-> (Int -> GroupS -> Text)
-> (GroupS -> Text)
-> ([GroupS] -> Text)
-> TextShow GroupS
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 :: [GroupS] -> Text
$cshowtlList :: [GroupS] -> Text
showtl :: GroupS -> Text
$cshowtl :: GroupS -> Text
showtlPrec :: Int -> GroupS -> Text
$cshowtlPrec :: Int -> GroupS -> Text
showtList :: [GroupS] -> Text
$cshowtList :: [GroupS] -> Text
showt :: GroupS -> Text
$cshowt :: GroupS -> Text
showtPrec :: Int -> GroupS -> Text
$cshowtPrec :: Int -> GroupS -> Text
showbList :: [GroupS] -> Builder
$cshowbList :: [GroupS] -> Builder
showb :: GroupS -> Builder
$cshowb :: GroupS -> Builder
showbPrec :: Int -> GroupS -> Builder
$cshowbPrec :: Int -> GroupS -> Builder
TextShow ) via TSG.FromGeneric GroupS
instance Show Group where
showsPrec :: Int -> Group -> ShowS
showsPrec d :: Int
d Group { NonEmpty Text
names :: NonEmpty Text
$sel:names:Group :: Group -> NonEmpty Text
names, Maybe Group
parent :: Maybe Group
$sel:parent:Group :: Group -> Maybe Group
parent, HashMap Text (Command, AliasType)
commands :: HashMap Text (Command, AliasType)
$sel:commands:Group :: Group -> HashMap Text (Command, AliasType)
commands, HashMap Text (Group, AliasType)
children :: HashMap Text (Group, AliasType)
$sel:children:Group :: Group -> HashMap Text (Group, AliasType)
children } = Int -> GroupS -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (GroupS -> ShowS) -> GroupS -> ShowS
forall a b. (a -> b) -> a -> b
$ NonEmpty Text
-> Maybe Text
-> HashMap Text (Command, AliasType)
-> HashMap Text (Group, AliasType)
-> GroupS
GroupS NonEmpty Text
names (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) HashMap Text (Command, AliasType)
commands HashMap Text (Group, AliasType)
children
instance TextShow Group where
showbPrec :: Int -> Group -> Builder
showbPrec d :: Int
d Group { NonEmpty Text
names :: NonEmpty Text
$sel:names:Group :: Group -> NonEmpty Text
names, Maybe Group
parent :: Maybe Group
$sel:parent:Group :: Group -> Maybe Group
parent, HashMap Text (Command, AliasType)
commands :: HashMap Text (Command, AliasType)
$sel:commands:Group :: Group -> HashMap Text (Command, AliasType)
commands, HashMap Text (Group, AliasType)
children :: HashMap Text (Group, AliasType)
$sel:children:Group :: Group -> HashMap Text (Group, AliasType)
children } = Int -> GroupS -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
d (GroupS -> Builder) -> GroupS -> Builder
forall a b. (a -> b) -> a -> b
$ NonEmpty Text
-> Maybe Text
-> HashMap Text (Command, AliasType)
-> HashMap Text (Group, AliasType)
-> GroupS
GroupS NonEmpty Text
names (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) HashMap Text (Command, AliasType)
commands HashMap Text (Group, AliasType)
children