Generate command table (#531)

Generate table for [Commands Cheat Sheet](https://github.com/swarm-game/swarm/wiki/Commands-Cheat-Sheet) Wiki.

- part of #344
This commit is contained in:
Ondřej Šebek 2022-07-04 10:47:55 +02:00 committed by GitHub
parent 45755c47d3
commit f2ad1322c9
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
8 changed files with 306 additions and 126 deletions

View File

@ -9,7 +9,7 @@ import Data.Text.IO qualified as Text
import GitHash (giBranch, giHash, tGitInfoCwdTry)
import Options.Applicative
import Swarm.App (appMain)
import Swarm.DocGen (EditorType (..), GenerateDocs (..), generateDocs)
import Swarm.DocGen (EditorType (..), GenerateDocs (..), SheetType (..), generateDocs)
import Swarm.Language.LSP (lspMain)
import Swarm.Language.Pipeline (processTerm)
import System.Exit (exitFailure, exitSuccess)
@ -44,6 +44,7 @@ cliParser =
subparser . mconcat $
[ command "recipes" (info (pure RecipeGraph) $ progDesc "Output graphviz dotfile of entity dependencies based on recipes")
, command "editors" (info (EditorKeywords <$> editor <**> helper) $ progDesc "Output editor keywords")
, command "cheatsheet" (info (pure $ CheatSheet $ Just Commands) $ progDesc "Output nice Wiki tables")
]
editor :: Parser (Maybe EditorType)
editor =

View File

@ -29,14 +29,20 @@
;; cabal run swarm:swarm -- generate editors --emacs
(x-keywords '("def" "end"))
(x-builtins '(
"self"
"parent"
"base"
"if"
"run"
"return"
"try"
"fail"
"force"
"inl"
"inr"
"case"
"fst"
"snd"
"force"
"undefined"
"fail"
"not"
"format"
))
(x-commands '(
"noop"
@ -66,18 +72,12 @@
"scan"
"upload"
"ishere"
"self"
"parent"
"base"
"whoami"
"setname"
"random"
"inl"
"inr"
"case"
"undefined"
"not"
"format"
"run"
"return"
"try"
"teleport"
"as"
"robotnamed"

View File

@ -56,7 +56,7 @@
},
{
"name": "keyword.other",
"match": "\\b(?i)(noop|wait|selfdestruct|move|turn|grab|harvest|place|give|install|make|has|count|drill|build|salvage|reprogram|say|log|view|appear|create|whereami|blocked|scan|upload|ishere|self|parent|base|whoami|setname|random|run|if|inl|inr|case|fst|snd|force|return|try|undefined|fail|not|format|teleport|as|robotnamed|robotnumbered|knows)\\b"
"match": "\\b(?i)(self|parent|base|if|inl|inr|case|fst|snd|force|undefined|fail|not|format|noop|wait|selfdestruct|move|turn|grab|harvest|place|give|install|make|has|count|drill|build|salvage|reprogram|say|log|view|appear|create|whereami|blocked|scan|upload|ishere|whoami|setname|random|run|return|try|teleport|as|robotnamed|robotnumbered|knows)\\b"
}
]
},

View File

@ -4,13 +4,17 @@ module Swarm.DocGen (
generateDocs,
GenerateDocs (..),
EditorType (..),
SheetType (..),
-- ** Formatted keyword lists
keywordsCommands,
keywordsDirections,
operatorNames,
builtinCommandsListEmacs,
builtinFunctionList,
editorList,
-- ** Wiki pages
commandsPage,
) where
import Control.Lens (view, (^.))
@ -19,6 +23,7 @@ import Control.Monad.Except (ExceptT, runExceptT)
import Data.Bifunctor (Bifunctor (bimap))
import Data.Containers.ListUtils (nubOrd)
import Data.Foldable (toList)
import Data.List (transpose)
import Data.Map.Lazy (Map)
import Data.Map.Lazy qualified as Map
import Data.Maybe (fromMaybe)
@ -34,8 +39,11 @@ import Swarm.Game.Recipe (Recipe, loadRecipes, recipeInputs, recipeOutputs, reci
import Swarm.Game.Robot (installedDevices, robotInventory, setRobotID)
import Swarm.Game.Scenario (Scenario, loadScenario, scenarioRobots)
import Swarm.Game.WorldGen (testWorld2Entites)
import Swarm.Language.Syntax (Const (..), ConstMeta (..))
import Swarm.Language.Capability (capabilityName, constCaps)
import Swarm.Language.Pretty (prettyText)
import Swarm.Language.Syntax (Const (..))
import Swarm.Language.Syntax qualified as Syntax
import Swarm.Language.Typecheck (inferConst)
import Swarm.Util (isRightOr)
import Text.Dot (Dot, NodeId, (.->.))
import Text.Dot qualified as Dot
@ -53,11 +61,15 @@ data GenerateDocs where
RecipeGraph :: GenerateDocs
-- | Keyword lists for editors.
EditorKeywords :: Maybe EditorType -> GenerateDocs
CheatSheet :: Maybe SheetType -> GenerateDocs
deriving (Eq, Show)
data EditorType = Emacs | VSCode
deriving (Eq, Show, Enum, Bounded)
data SheetType = Entities | Commands | Capabilities | Recipes
deriving (Eq, Show, Enum, Bounded)
generateDocs :: GenerateDocs -> IO ()
generateDocs = \case
RecipeGraph -> generateRecipe >>= putStrLn
@ -72,6 +84,11 @@ generateDocs = \case
putStrLn $ replicate 40 '-'
generateEditorKeywords et
mapM_ editorGen [minBound .. maxBound]
CheatSheet s -> case s of
Nothing -> error "Not implemented"
Just st -> case st of
Commands -> T.putStrLn commandsPage
_ -> error "Not implemented"
-- ----------------------------------------------------------------------------
-- GENERATE KEYWORDS: LIST OF WORDS TO BE HIGHLIGHTED
@ -81,24 +98,30 @@ generateEditorKeywords :: EditorType -> IO ()
generateEditorKeywords = \case
Emacs -> do
putStrLn "(x-builtins '("
T.putStr . editorList Emacs $ map constSyntax builtinCommandsEmacs
T.putStr $ builtinFunctionList Emacs
putStrLn "))\n(x-commands '("
T.putStr $ keywordsCommands Emacs
T.putStr $ keywordsDirections Emacs
putStrLn "))"
VSCode -> do
putStrLn "Functions and commands:"
T.putStrLn $ keywordsCommands VSCode
T.putStrLn $ builtinFunctionList VSCode <> "|" <> keywordsCommands VSCode
putStrLn "\nDirections:"
T.putStrLn $ keywordsDirections VSCode
putStrLn "\nOperators:"
T.putStrLn operatorNames
builtinCommandsEmacs :: [Const]
builtinCommandsEmacs = [If, Run, Return, Try, Fail, Force, Fst, Snd]
commands :: [Const]
commands = filter Syntax.isCmd Syntax.allConst
builtinCommandsListEmacs :: Text
builtinCommandsListEmacs = editorList Emacs $ map constSyntax builtinCommandsEmacs
operators :: [Const]
operators = filter Syntax.isOperator Syntax.allConst
builtinFunctions :: [Const]
builtinFunctions = filter Syntax.isBuiltinFunction Syntax.allConst
builtinFunctionList :: EditorType -> Text
builtinFunctionList e = editorList e $ map constSyntax builtinFunctions
editorList :: EditorType -> [Text] -> Text
editorList = \case
@ -112,16 +135,14 @@ constSyntax = Syntax.syntax . Syntax.constInfo
-- | Get formatted list of basic functions/commands.
keywordsCommands :: EditorType -> Text
keywordsCommands e = editorList e $ map constSyntax (filter isFunc Syntax.allConst)
where
isFunc c = Syntax.isUserFunc c && (e /= Emacs || c `notElem` builtinCommandsEmacs)
keywordsCommands e = editorList e $ map constSyntax commands
-- | Get formatted list of directions.
keywordsDirections :: EditorType -> Text
keywordsDirections e = editorList e $ map (Syntax.dirSyntax . Syntax.dirInfo) Syntax.allDirs
operatorNames :: Text
operatorNames = T.intercalate "|" $ map (escape . constSyntax) (filter isOperator Syntax.allConst)
operatorNames = T.intercalate "|" $ map (escape . constSyntax) operators
where
special :: String
special = "*+$[]|^"
@ -129,10 +150,84 @@ operatorNames = T.intercalate "|" $ map (escape . constSyntax) (filter isOperato
'/' -> "/(?![/|*])"
c -> T.singleton c
escape = T.concatMap (\c -> if c `elem` special then T.snoc "\\\\" c else slashNotComment c)
isOperator c = case Syntax.constMeta $ Syntax.constInfo c of
ConstMUnOp {} -> True
ConstMBinOp {} -> True
ConstMFunc {} -> False
-- ----------------------------------------------------------------------------
-- GENERATE TABLES: COMMANDS, ENTITIES AND CAPABILITIES TO MARKDOWN TABLE
-- ----------------------------------------------------------------------------
wrap :: Char -> Text -> Text
wrap c = T.cons c . flip T.snoc c
codeQuote :: Text -> Text
codeQuote = wrap '`'
escapeTable :: Text -> Text
escapeTable = T.concatMap (\c -> if c == '|' then T.snoc "\\" c else T.singleton c)
separatingLine :: [Int] -> Text
separatingLine ws = T.cons '|' . T.concat $ map (flip T.snoc '|' . flip T.replicate "-" . (2 +)) ws
listToRow :: [Int] -> [Text] -> Text
listToRow mw xs = wrap '|' . T.intercalate "|" $ zipWith format mw xs
where
format w x = wrap ' ' x <> T.replicate (w - T.length x) " "
maxWidths :: [[Text]] -> [Int]
maxWidths = map (maximum . map T.length) . transpose
-- ---------
-- COMMANDS
-- ---------
commandHeader :: [Text]
commandHeader = ["Syntax", "Type", "Capability", "Description"]
commandToList :: Const -> [Text]
commandToList c =
map
escapeTable
[ addLink (T.pack $ "#" <> show c) . codeQuote $ constSyntax c
, codeQuote . prettyText $ inferConst c
, maybe "" capabilityName $ constCaps c
, Syntax.briefDoc . Syntax.constDoc $ Syntax.constInfo c
]
where
addLink l t = T.concat ["[", t, "](", l, ")"]
constTable :: [Const] -> Text
constTable cs = T.unlines $ header <> map (listToRow mw) commandRows
where
mw = maxWidths (commandHeader : commandRows)
commandRows = map commandToList cs
header = [listToRow mw commandHeader, separatingLine mw]
commandToSection :: Const -> Text
commandToSection c =
T.unlines $
[ "## " <> T.pack (show c)
, ""
, "- syntax: " <> codeQuote (constSyntax c)
, "- type: " <> (codeQuote . prettyText $ inferConst c)
, maybe "" (("- required capabilities: " <>) . capabilityName) $ constCaps c
, ""
, Syntax.briefDoc . Syntax.constDoc $ Syntax.constInfo c
]
<> let l = Syntax.longDoc . Syntax.constDoc $ Syntax.constInfo c
in if T.null l then [] else ["", l]
commandsPage :: Text
commandsPage =
T.intercalate "\n\n" $
[ "# Commands"
, constTable commands
, "# Builtin functions"
, "These functions are evaluated immediately once they have enough arguments."
, constTable builtinFunctions
, "# Operators"
, constTable operators
, "# Detailed descriptions"
]
<> map commandToSection (commands <> builtinFunctions <> operators)
-- ----------------------------------------------------------------------------
-- GENERATE GRAPHVIZ: ENTITY DEPENDENCIES BY RECIPES

View File

@ -30,6 +30,7 @@ module Swarm.Language.Syntax (
Const (..),
allConst,
ConstInfo (..),
ConstDoc (..),
ConstMeta (..),
MBinAssoc (..),
MUnAssoc (..),
@ -37,6 +38,8 @@ module Swarm.Language.Syntax (
arity,
isCmd,
isUserFunc,
isOperator,
isBuiltinFunction,
-- * Syntax
Syntax (..),
@ -65,22 +68,21 @@ module Swarm.Language.Syntax (
) where
import Control.Lens (Plated (..), Traversal', (%~))
import Data.Data.Lens (uniplate)
import Data.Int (Int64)
import Data.Map qualified as M
import Data.Set qualified as S
import Data.Text hiding (filter, map)
import Data.Text qualified as T
import Linear
import Data.Aeson.Types
import Data.Data (Data)
import Data.Data.Lens (uniplate)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import Witch.From (from)
import Data.Int (Int64)
import Data.Map qualified as M
import Data.Maybe (fromMaybe, isJust, mapMaybe)
import Data.Set qualified as S
import Data.String (IsString (fromString))
import Data.Text hiding (filter, map)
import Data.Text qualified as T
import GHC.Generics (Generic)
import Linear
import Swarm.Language.Types
import Witch.From (from)
------------------------------------------------------------
-- Constants
@ -196,7 +198,7 @@ data Const
-- | Do nothing. This is different than 'Wait'
-- in that it does not take up a time step.
Noop
| -- | Wait for one time step without doing anything.
| -- | Wait for a number of time steps without doing anything.
Wait
| -- | Self-destruct.
Selfdestruct
@ -362,9 +364,16 @@ data ConstInfo = ConstInfo
{ syntax :: Text
, fixity :: Int
, constMeta :: ConstMeta
, constDoc :: ConstDoc
}
deriving (Eq, Ord, Show)
data ConstDoc = ConstDoc {briefDoc :: Text, longDoc :: Text}
deriving (Eq, Ord, Show)
instance IsString ConstDoc where
fromString = flip ConstDoc "" . T.pack
data ConstMeta
= -- | Function with arity of which some are commands
ConstMFunc Int Bool
@ -419,6 +428,23 @@ isUserFunc c = case constMeta $ constInfo c of
ConstMFunc {} -> True
_ -> False
-- | Whether the constant is an operator. Useful predicate for documentation.
isOperator :: Const -> Bool
isOperator c = case constMeta $ constInfo c of
ConstMUnOp {} -> True
ConstMBinOp {} -> True
ConstMFunc {} -> False
-- | Whether the constant is a /function/ which is interpreted as soon
-- as it is evaluated, but *not* including operators.
--
-- Note: This is used for documentation purposes and complements 'isCmd'
-- and 'isOperator' in that exactly one will accept a given constant.
isBuiltinFunction :: Const -> Bool
isBuiltinFunction c = case constMeta $ constInfo c of
ConstMFunc _ cmd -> not cmd
_ -> False
-- | Information about constants used in parsing and pretty printing.
--
-- It would be more compact to represent the information by testing
@ -426,79 +452,131 @@ isUserFunc c = case constMeta $ constInfo c of
-- matching gives us warning if we add more constants.
constInfo :: Const -> ConstInfo
constInfo c = case c of
Wait -> commandLow 0
Noop -> commandLow 0
Selfdestruct -> commandLow 0
Move -> commandLow 0
Turn -> commandLow 1
Grab -> commandLow 0
Harvest -> commandLow 0
Place -> commandLow 1
Give -> commandLow 2
Install -> commandLow 2
Make -> commandLow 1
Has -> commandLow 1
Count -> commandLow 1
Reprogram -> commandLow 2
Drill -> commandLow 1
Build -> commandLow 2
Salvage -> commandLow 0
Say -> commandLow 1
Log -> commandLow 1
View -> commandLow 1
Appear -> commandLow 1
Create -> commandLow 1
Whereami -> commandLow 0
Blocked -> commandLow 0
Scan -> commandLow 0
Upload -> commandLow 1
Ishere -> commandLow 1
Self -> functionLow 0
Parent -> functionLow 0
Base -> functionLow 0
Whoami -> commandLow 0
Setname -> commandLow 1
Random -> commandLow 1
Run -> commandLow 1
Return -> commandLow 1
Try -> commandLow 2
Undefined -> functionLow 0
Fail -> functionLow 1
If -> functionLow 3
Inl -> functionLow 1
Inr -> functionLow 1
Case -> functionLow 3
Fst -> functionLow 1
Snd -> functionLow 1
Force -> functionLow 1
Not -> functionLow 1
Neg -> unaryOp "-" 7 P
Add -> binaryOp "+" 6 L
And -> binaryOp "&&" 3 R
Or -> binaryOp "||" 2 R
Sub -> binaryOp "-" 6 L
Mul -> binaryOp "*" 7 L
Div -> binaryOp "/" 7 L
Exp -> binaryOp "^" 8 R
Eq -> binaryOp "==" 4 N
Neq -> binaryOp "!=" 4 N
Lt -> binaryOp "<" 4 N
Gt -> binaryOp ">" 4 N
Leq -> binaryOp "<=" 4 N
Geq -> binaryOp ">=" 4 N
Format -> functionLow 1
Concat -> binaryOp "++" 6 R
AppF -> binaryOp "$" 0 R
Teleport -> commandLow 2
As -> commandLow 2
RobotNamed -> commandLow 1
RobotNumbered -> commandLow 1
Knows -> commandLow 1
Wait -> commandLow 0 "Wait for a number of time steps."
Noop ->
commandLow 0 . doc "Do nothing." $
[ "This is different than `Wait` in that it does not take up a time step."
, "It is useful for commands like if, which requires you to provide both branches."
, "Usually it is automatically inserted where needed, so you do not have to worry about it."
]
Selfdestruct ->
commandLow 0 . doc "Self-destruct the robot." $
[ "Useful to not clutter the world."
, "This destroys the robot's inventory, so consider `salvage` as an alternative."
]
Move -> commandLow 0 "Move forward one step."
Turn -> commandLow 1 "Turn in some direction."
Grab -> commandLow 0 "Grab an item from the current location."
Harvest ->
commandLow 0 . doc "Harvest an item from the current location." $
[ "Leaves behind a growing seed if the harvested item is growable."
, "Otherwise it works exactly like `grab`."
]
Place ->
commandLow 1 . doc "Place an item at the current location." $
["The current location has to be empty for this to work."]
Give -> commandLow 2 "Give an item to another robot nearby."
Install -> commandLow 2 "Install a device from inventory on a robot."
Make -> commandLow 1 "Make an item using a recipe."
Has -> commandLow 1 "Sense whether the robot has a given item in its inventory."
Count -> commandLow 1 "Get the count of a given item in a robot's inventory."
Reprogram ->
commandLow 2 . doc "Reprogram another robot with a new command." $
["The other robot has to be nearby and idle."]
Drill ->
commandLow 1 . doc "Drill through an entity." $
[ "Usually you want to `drill forward` when exploring to clear out obstacles."
, "When you have found a source to drill, you can stand on it and `drill down`."
, "See what recipes with drill you have available."
]
Build ->
commandLow 1 . doc "Construct a new robot." $
[ "You can specify a command for the robot to execute."
, "If the command requires devices they will be installed from your inventory."
]
Salvage ->
commandLow 0 . doc "Deconstruct an old robot." $
["Salvaging a robot will give you its inventory, installed devices and log."]
Say ->
commandLow 1 . doc "Emit a message." $ -- TODO: #513
[ "The message will be in a global log, which you can not currently view."
, "https://github.com/swarm-game/swarm/issues/513"
]
Log -> commandLow 1 "Log the string in the robot's logger."
View -> commandLow 1 "View the given robot."
Appear ->
commandLow 1 . doc "Set how the robot is displayed." $
[ "You can either specify one character or five (for each direction)."
, "The default is \"X^>v<\"."
]
Create ->
commandLow 1 . doc "Create an item out of thin air." $
["Only available in creative mode."]
Whereami -> commandLow 0 "Get the current x and y coordinates."
Blocked -> commandLow 0 "See if the robot can move forward."
Scan ->
commandLow 0 . doc "Scan a nearby location for entities." $
[ "Adds the entity (not robot) to your inventory with count 0 if there is any."
, "If you can use sum types, you can also inspect the result directly."
]
Upload -> commandLow 1 "Upload a robot's known entities and log to another robot."
Ishere -> commandLow 1 "See if a specific entity is in the current location."
Self -> functionLow 0 "Get a reference to the current robot."
Parent -> functionLow 0 "Get a reference to the robot's parent."
Base -> functionLow 0 "Get a reference to the base."
Whoami -> commandLow 0 "Get the robot's display name."
Setname -> commandLow 1 "Set the robot's display name."
Random ->
commandLow 1 . doc "Get a uniformly random integer." $
["The random integer will be chosen from the range 0 to n-1, exclusive of the argument."]
Run -> commandLow 1 "Run a program loaded from a file."
Return -> commandLow 1 "Make the value a result in `cmd`."
Try -> commandLow 2 "Execute a command, catching errors."
Undefined -> functionLow 0 "A value of any type, that is evaluated as error."
Fail -> functionLow 1 "A value of any type, that is evaluated as error with message."
If ->
functionLow 3 . doc "If-Then-Else function." $
["If the bool predicate is true then evaluate the first expression, otherwise the second."]
Inl -> functionLow 1 "Put the value into the left component of a sum type."
Inr -> functionLow 1 "Put the value into the right component of a sum type."
Case -> functionLow 3 "Evaluate one of the given functions on a value of sum type."
Fst -> functionLow 1 "Get the first value of a pair."
Snd -> functionLow 1 "Get the second value of a pair."
Force -> functionLow 1 "Force the evaluation of a delayed value."
Not -> functionLow 1 "Negate the boolean value."
Neg -> unaryOp "-" 7 P "Negate the given integer value."
Add -> binaryOp "+" 6 L "Add the given integer values."
And -> binaryOp "&&" 3 R "Logical and (true if both values are true)."
Or -> binaryOp "||" 2 R "Logical or (true if either value is true)."
Sub -> binaryOp "-" 6 L "Subtract the given integer values."
Mul -> binaryOp "*" 7 L "Multiply the given integer values."
Div -> binaryOp "/" 7 L "Divide the left integer value by the right one, rounding down."
Exp -> binaryOp "^" 8 R "Raise the left integer value to the power of the right one."
Eq -> binaryOp "==" 4 N "Check that the left value is equal to the right one."
Neq -> binaryOp "!=" 4 N "Check that the left value is not equal to the right one."
Lt -> binaryOp "<" 4 N "Check that the left value is lesser than the right one."
Gt -> binaryOp ">" 4 N "Check that the left value is greater than the right one."
Leq -> binaryOp "<=" 4 N "Check that the left value is lesser or equal to the right one."
Geq -> binaryOp ">=" 4 N "Check that the left value is greater or equal to the right one."
Format -> functionLow 1 "Turn an arbitrary value into a string."
Concat -> binaryOp "++" 6 R "Concatenate the given strings."
AppF ->
binaryOp "$" 0 R . doc "Apply the function on the left to the value on the right." $
[ "This operator is useful to avoid nesting parentheses."
, "For exaple:"
, "`f $ g $ h x = f (g (h x))`"
]
Teleport -> commandLow 2 "Teleport a robot to the given location."
As -> commandLow 2 "Hypothetically run a command as if you were another robot."
RobotNamed -> commandLow 1 "Find a robot by name."
RobotNumbered -> commandLow 1 "Find a robot by number."
Knows -> commandLow 1 "Check if the robot knows about an entity."
where
unaryOp s p side = ConstInfo {syntax = s, fixity = p, constMeta = ConstMUnOp side}
binaryOp s p side = ConstInfo {syntax = s, fixity = p, constMeta = ConstMBinOp side}
command s a = ConstInfo {syntax = s, fixity = 11, constMeta = ConstMFunc a True}
function s a = ConstInfo {syntax = s, fixity = 11, constMeta = ConstMFunc a False}
doc b ls = ConstDoc b (T.unlines ls)
unaryOp s p side d = ConstInfo {syntax = s, fixity = p, constMeta = ConstMUnOp side, constDoc = d}
binaryOp s p side d = ConstInfo {syntax = s, fixity = p, constMeta = ConstMBinOp side, constDoc = d}
command s a d = ConstInfo {syntax = s, fixity = 11, constMeta = ConstMFunc a True, constDoc = d}
function s a d = ConstInfo {syntax = s, fixity = 11, constMeta = ConstMFunc a False, constDoc = d}
-- takes the number of arguments for a commmand
commandLow = command (lowShow c)
functionLow = function (lowShow c)

View File

@ -312,7 +312,7 @@ inferModule s@(Syntax _ t) = (`catchError` addLocToTypeErr s) $ case t of
infer :: Syntax -> Infer UType
infer s@(Syntax l t) = (`catchError` addLocToTypeErr s) $ case t of
TUnit -> return UTyUnit
TConst c -> instantiate $ inferConst c
TConst c -> instantiate . toU $ inferConst c
TDir _ -> return UTyDir
TInt _ -> return UTyInt
TAntiInt _ -> return UTyInt
@ -425,8 +425,8 @@ decomposeFunTy ty = do
return (ty1, ty2)
-- | Infer the type of a constant.
inferConst :: Const -> UPolytype
inferConst c = toU $ case c of
inferConst :: Const -> Polytype
inferConst c = case c of
Wait -> [tyQ| int -> cmd () |]
Noop -> [tyQ| cmd () |]
Selfdestruct -> [tyQ| cmd () |]

View File

@ -75,10 +75,10 @@ import Swarm.Game.Scenario (ScenarioItem (..), scenarioDescription, scenarioItem
import Swarm.Game.State
import Swarm.Game.Terrain (displayTerrain)
import Swarm.Game.World qualified as W
import Swarm.Language.Pipeline (ProcessedTerm (..), processParsedTerm)
import Swarm.Language.Pretty (prettyText)
import Swarm.Language.Syntax
import Swarm.Language.Types (Module (..), Polytype)
import Swarm.Language.Typecheck (inferConst)
import Swarm.Language.Types (Polytype)
import Swarm.TUI.Attr
import Swarm.TUI.Border
import Swarm.TUI.Model
@ -466,7 +466,7 @@ availableListWidget gs nl = viewport vp Vertical (padTop (Pad 1) $ vBox $ addHea
where
(vp, widgetList, addHeader) = case nl of
RecipeList -> (RecipesViewport, mkAvailableList gs availableRecipes renderRecipe, id)
CommandList -> (CommandsViewport, mkAvailableList gs availableCommands renderCommand, (padLeftRight 18 constHeader :))
CommandList -> (CommandsViewport, mkAvailableList gs availableCommands renderCommand, (<> constWiki) . (padLeftRight 18 constHeader :))
renderRecipe = padLeftRight 18 . drawRecipe Nothing (fromMaybe E.empty inv)
inv = gs ^? to focusedRobot . _Just . robotInventory
renderCommand = padLeftRight 18 . drawConst
@ -486,13 +486,18 @@ mkAvailableList gs notifLens notifRender = map padRender news <> notifSep <> map
constHeader :: Widget Name
constHeader = padBottom (Pad 1) $ withAttr robotAttr $ padLeft (Pad 1) $ txt "command name : type"
constWiki :: [Widget Name]
constWiki =
padLeftRight 13
<$> [ padTop (Pad 2) $ txt "For the full list of available commands see the Wiki at:"
, txt "https://github.com/swarm-game/swarm/wiki/Commands-Cheat-Sheet"
]
drawConst :: Const -> Widget Name
drawConst c = hBox [padLeft (Pad $ 13 - T.length constName) (txt constName), txt constSig]
where
constName = syntax . constInfo $ c
constSig = case processParsedTerm (noLoc $ TConst c) of
Right (ProcessedTerm (TConst _) (Module pt _) _ _) -> " : " <> prettyText pt
_ -> "??"
constSig = " : " <> prettyText (inferConst c)
descriptionTitle :: Entity -> String
descriptionTitle e = " " ++ from @Text (e ^. entityName) ++ " "

View File

@ -228,12 +228,13 @@ testEditorFiles =
[ testGroup
"VS Code"
[ testTextInVSCode "operators" (const DocGen.operatorNames)
, testTextInVSCode "builtin" DocGen.builtinFunctionList
, testTextInVSCode "commands" DocGen.keywordsCommands
, testTextInVSCode "directions" DocGen.keywordsDirections
]
, testGroup
"Emacs"
[ testTextInEmacs "builtin" (const DocGen.builtinCommandsListEmacs)
[ testTextInEmacs "builtin" DocGen.builtinFunctionList
, testTextInEmacs "commands" DocGen.keywordsCommands
, testTextInEmacs "directions" DocGen.keywordsDirections
]