Skip to content

Commit

Permalink
Render command matrix
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Nov 23, 2023
1 parent 44c2e60 commit f415529
Show file tree
Hide file tree
Showing 15 changed files with 541 additions and 144 deletions.
1 change: 1 addition & 0 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -135,6 +135,7 @@ cliParser =
, Just Recipes <$ switch (long "recipes" <> help "Generate recipes page (uses data from recipes.yaml)")
, Just Capabilities <$ switch (long "capabilities" <> help "Generate capabilities page (uses entity map)")
, Just Commands <$ switch (long "commands" <> help "Generate commands page (uses constInfo, constCaps and inferConst)")
, Just CommandMatrix <$ switch (long "matrix" <> help "Generate commands matrix page")
, Just Scenario <$ switch (long "scenario" <> help "Generate scenario schema page")
]
seed :: Parser (Maybe Int)
Expand Down
4 changes: 1 addition & 3 deletions src/Swarm/Doc/Schema/Render.hs
Original file line number Diff line number Diff line change
Expand Up @@ -111,9 +111,7 @@ recombineExtension (filenameStem, fileExtension) =

genMarkdown :: [SchemaData] -> Either T.Text T.Text
genMarkdown schemaThings =
left renderError $
runPure $
writeMarkdown (def {writerExtensions = extensionsFromList [Ext_pipe_tables]}) pd
pandocToText pd
where
titleMap = makeTitleMap schemaThings
pd =
Expand Down
8 changes: 8 additions & 0 deletions src/Swarm/Doc/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
-- Utilities for generating doc markup
module Swarm.Doc.Util where

import Control.Arrow (left)
import Control.Effect.Throw (Has, Throw, throwError)
import Control.Lens (view)
import Data.Maybe (listToMaybe)
Expand All @@ -16,6 +17,7 @@ import Swarm.Game.Robot (Robot, instantiateRobot)
import Swarm.Game.Scenario (Scenario, scenarioRobots)
import Swarm.Language.Syntax (Const (..))
import Swarm.Language.Syntax qualified as Syntax
import Text.Pandoc

-- * Text operations

Expand Down Expand Up @@ -51,3 +53,9 @@ getBaseRobot :: Has (Throw SystemFailure) sig m => Scenario -> m Robot
getBaseRobot s = case listToMaybe $ view scenarioRobots s of
Just r -> pure $ instantiateRobot 0 r
Nothing -> throwError $ CustomFailure "Scenario contains no robots"

pandocToText :: Pandoc -> Either Text Text
pandocToText =
left renderError
. runPure
. writeMarkdown (def {writerExtensions = extensionsFromList [Ext_pipe_tables]})
6 changes: 5 additions & 1 deletion src/Swarm/Doc/Wiki/Cheatsheet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ import Data.Text qualified as T
import Data.Text.IO qualified as T
import Swarm.Doc.Schema.Render
import Swarm.Doc.Util
import Swarm.Doc.Wiki.Matrix
import Swarm.Game.Display (displayChar)
import Swarm.Game.Entity (Entity, EntityMap (entitiesByName), entityDisplay, entityName, loadEntities)
import Swarm.Game.Entity qualified as E
Expand Down Expand Up @@ -52,7 +53,7 @@ data PageAddress = PageAddress
deriving (Eq, Show)

-- | An enumeration of the kinds of cheat sheets we can produce.
data SheetType = Entities | Commands | Capabilities | Recipes | Scenario
data SheetType = Entities | Commands | CommandMatrix | Capabilities | Recipes | Scenario
deriving (Eq, Show, Enum, Bounded)

-- * Functions
Expand All @@ -62,6 +63,9 @@ makeWikiPage address s = case s of
Nothing -> error "Not implemented for all Wikis"
Just st -> case st of
Commands -> T.putStrLn commandsPage
CommandMatrix -> case pandocToText commandsMatrix of
Right x -> T.putStrLn x
Left x -> error $ T.unpack x
Capabilities -> simpleErrorHandle $ do
entities <- loadEntities
sendIO $ T.putStrLn $ capabilityPage address entities
Expand Down
92 changes: 92 additions & 0 deletions src/Swarm/Doc/Wiki/Matrix.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,92 @@
{-# LANGUAGE OverloadedStrings #-}

-- |
-- SPDX-License-Identifier: BSD-3-Clause
--
-- Auto-generation of command attributes matrix.
module Swarm.Doc.Wiki.Matrix where

import Data.Aeson (ToJSON)
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import GHC.Generics (Generic)
import Servant.Docs qualified as SD
import Swarm.Doc.Util
import Swarm.Language.Pretty (unchainFun)
import Swarm.Language.Syntax
import Swarm.Language.Syntax.CommandMetadata
import Swarm.Language.Typecheck (inferConst)
import Swarm.Language.Types
import Text.Pandoc
import Text.Pandoc.Builder

data DerivedAttrs = DerivedAttrs
{ hasActorTarget :: Bool
, pureComputation :: Bool
}
deriving (Generic, ToJSON)

data CommandEntry = CommandEntry
{ cmd :: Const
, effects :: CommandEffect
, argTypes :: NE.NonEmpty Type
, derivedAttrs :: DerivedAttrs
}
deriving (Generic, ToJSON)

newtype CommandCatalog = CommandCatalog
{ entries :: [CommandEntry]
}
deriving (Generic, ToJSON)

instance SD.ToSample CommandCatalog where
toSamples _ = SD.noSamples

mkEntry :: Const -> CommandEntry
mkEntry c =
CommandEntry c cmdEffects rawArgs $
DerivedAttrs
(operatesOnActor inputArgs)
(cmdEffects == Computation)
where
cmdInfo = constInfo c
cmdEffects = effectInfo $ constDoc cmdInfo

getArgs ((Forall _ t)) = unchainFun t

rawArgs = getArgs $ inferConst c

inputArgs = NE.init rawArgs
outputType = NE.last rawArgs

operatesOnActor = elem TyActor

getCatalog :: CommandCatalog
getCatalog = CommandCatalog $ map mkEntry commands

commandsMatrix :: Pandoc
commandsMatrix =
setTitle (text "Commands matrix") $
doc (header 3 (text "Commands matrix"))
<> doc (makePropsTable ["Command", "Effects", "Actor Target", "Type"])

makePropsTable ::
[T.Text] ->
Blocks
makePropsTable headingsList =
simpleTable headerRow $ map genPropsRow catalogEntries
where
CommandCatalog catalogEntries = getCatalog
headerRow = map (plain . text) headingsList

genPropsRow :: CommandEntry -> [Blocks]
genPropsRow e =
[ showCode (cmd e)
, showCode (effects e)
, showCode (hasActorTarget $ derivedAttrs e)
]
<> NE.toList completeTypeMembers
where
showCode :: Show a => a -> Blocks
showCode = plain . code . T.pack . show
completeTypeMembers = NE.map showCode $ argTypes e
Loading

0 comments on commit f415529

Please sign in to comment.