{-# LANGUAGE OverloadedStrings #-}
module Swarm.Doc.Wiki.Matrix where
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Swarm.Doc.Command
import Text.Pandoc
import Text.Pandoc.Builder
commandsMatrix :: Pandoc
commandsMatrix :: Pandoc
commandsMatrix =
Inlines -> Pandoc -> Pandoc
setTitle (Text -> Inlines
text Text
"Commands matrix") (Pandoc -> Pandoc) -> Pandoc -> Pandoc
forall a b. (a -> b) -> a -> b
$
Blocks -> Pandoc
doc (Int -> Inlines -> Blocks
header Int
3 (Text -> Inlines
text Text
"Commands matrix"))
Pandoc -> Pandoc -> Pandoc
forall a. Semigroup a => a -> a -> a
<> Blocks -> Pandoc
doc ([Text] -> Blocks
makePropsTable [Text
"Command", Text
"Effects", Text
"Actor Target", Text
"Type"])
makePropsTable ::
[T.Text] ->
Blocks
makePropsTable :: [Text] -> Blocks
makePropsTable [Text]
headingsList =
[Blocks] -> [[Blocks]] -> Blocks
simpleTable [Blocks]
headerRow ([[Blocks]] -> Blocks) -> [[Blocks]] -> Blocks
forall a b. (a -> b) -> a -> b
$ (CommandEntry -> [Blocks]) -> [CommandEntry] -> [[Blocks]]
forall a b. (a -> b) -> [a] -> [b]
map CommandEntry -> [Blocks]
genPropsRow [CommandEntry]
catalogEntries
where
CommandCatalog [CommandEntry]
catalogEntries = CommandCatalog
getCatalog
headerRow :: [Blocks]
headerRow = (Text -> Blocks) -> [Text] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map (Inlines -> Blocks
plain (Inlines -> Blocks) -> (Text -> Inlines) -> Text -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
text) [Text]
headingsList
genPropsRow :: CommandEntry -> [Blocks]
genPropsRow :: CommandEntry -> [Blocks]
genPropsRow CommandEntry
e =
[ Const -> Blocks
forall a. Show a => a -> Blocks
showCode (CommandEntry -> Const
cmd CommandEntry
e)
, Set CommandEffect -> Blocks
forall a. Show a => a -> Blocks
showCode (CommandEntry -> Set CommandEffect
effects CommandEntry
e)
, Bool -> Blocks
forall a. Show a => a -> Blocks
showCode (DerivedAttrs -> Bool
hasActorTarget (DerivedAttrs -> Bool) -> DerivedAttrs -> Bool
forall a b. (a -> b) -> a -> b
$ CommandEntry -> DerivedAttrs
derivedAttrs CommandEntry
e)
]
[Blocks] -> [Blocks] -> [Blocks]
forall a. Semigroup a => a -> a -> a
<> NonEmpty Blocks -> [Blocks]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty Blocks
completeTypeMembers
where
showCode :: Show a => a -> Blocks
showCode :: forall a. Show a => a -> Blocks
showCode = Inlines -> Blocks
plain (Inlines -> Blocks) -> (a -> Inlines) -> a -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
code (Text -> Inlines) -> (a -> Text) -> a -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
completeTypeMembers :: NonEmpty Blocks
completeTypeMembers = (Type -> Blocks) -> NonEmpty Type -> NonEmpty Blocks
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map Type -> Blocks
forall a. Show a => a -> Blocks
showCode (NonEmpty Type -> NonEmpty Blocks)
-> NonEmpty Type -> NonEmpty Blocks
forall a b. (a -> b) -> a -> b
$ CommandEntry -> NonEmpty Type
argTypes CommandEntry
e