Skip to content

Commit b8d37a9

Browse files
authored
extract doc generator to separate executable (#1671)
Closes #1443. Also added `-Wunused-packages` to clean up dependencies. ## Demo This still works as usual: stack run Output editor keywords: stack run swarm-docs -- editors --emacs
1 parent 437f704 commit b8d37a9

File tree

15 files changed

+181
-130
lines changed

15 files changed

+181
-130
lines changed

app/Main.hs

-46
Original file line numberDiff line numberDiff line change
@@ -7,16 +7,13 @@
77
module Main where
88

99
import Data.Foldable qualified
10-
import Data.Maybe (fromMaybe)
1110
import Data.Text (Text, pack)
12-
import Data.Text qualified as T
1311
import Data.Text.IO qualified as Text
1412
import GitHash (GitInfo, giBranch, giHash, tGitInfoCwdTry)
1513
import Options.Applicative
1614
import Prettyprinter
1715
import Prettyprinter.Render.Text qualified as RT
1816
import Swarm.App (appMain)
19-
import Swarm.Doc.Gen (EditorType (..), GenerateDocs (..), PageAddress (..), SheetType (..), generateDocs)
2017
import Swarm.Game.Scenario.Topography.Area (AreaDimensions (..))
2118
import Swarm.Game.World.Render (OuputFormat (..), RenderOpts (..), doRenderCmd)
2219
import Swarm.Language.LSP (lspMain)
@@ -45,7 +42,6 @@ type Width = Int
4542
data CLI
4643
= Run AppOpts
4744
| Format Input (Maybe Width)
48-
| DocGen GenerateDocs
4945
| RenderMap FilePath RenderOpts
5046
| LSP
5147
| Version
@@ -55,7 +51,6 @@ cliParser =
5551
subparser
5652
( mconcat
5753
[ command "format" (info (Format <$> format <*> optional widthOpt <**> helper) (progDesc "Format a file"))
58-
, command "generate" (info (DocGen <$> docgen <**> helper) (progDesc "Generate docs"))
5954
, command "map" (info (render <**> helper) (progDesc "Render a scenario world map."))
6055
, command "lsp" (info (pure LSP) (progDesc "Start the LSP"))
6156
, command "version" (info (pure Version) (progDesc "Get current and upstream version."))
@@ -97,46 +92,6 @@ cliParser =
9792
widthOpt :: Parser Width
9893
widthOpt = option auto (long "width" <> metavar "COLUMNS" <> help "Use layout with maximum width")
9994

100-
docgen :: Parser GenerateDocs
101-
docgen =
102-
subparser . mconcat $
103-
[ command "recipes" (info (pure RecipeGraph) $ progDesc "Output graphviz dotfile of entity dependencies based on recipes")
104-
, command "editors" (info (EditorKeywords <$> editor <**> helper) $ progDesc "Output editor keywords")
105-
, command "keys" (info (pure SpecialKeyNames) $ progDesc "Output list of recognized special key names")
106-
, command "cheatsheet" (info (CheatSheet <$> address <*> cheatsheet <**> helper) $ progDesc "Output nice Wiki tables")
107-
, command "pedagogy" (info (pure TutorialCoverage) $ progDesc "Output tutorial coverage")
108-
, command "endpoints" (info (pure WebAPIEndpoints) $ progDesc "Generate markdown Web API documentation.")
109-
]
110-
111-
editor :: Parser (Maybe EditorType)
112-
editor =
113-
Data.Foldable.asum
114-
[ pure Nothing
115-
, Just VSCode <$ switch (long "code" <> help "Generate for the VS Code editor")
116-
, Just Emacs <$ switch (long "emacs" <> help "Generate for the Emacs editor")
117-
]
118-
address :: Parser PageAddress
119-
address =
120-
let replace a b = T.unpack . T.replace a b . T.pack
121-
opt n =
122-
fmap (fromMaybe "") . optional $
123-
option
124-
str
125-
( long n
126-
<> metavar "ADDRESS"
127-
<> help ("Set the address of " <> replace "-" " " n <> ". Default no link.")
128-
)
129-
in PageAddress <$> opt "entities-page" <*> opt "commands-page" <*> opt "capabilities-page" <*> opt "recipes-page"
130-
cheatsheet :: Parser (Maybe SheetType)
131-
cheatsheet =
132-
Data.Foldable.asum
133-
[ pure Nothing
134-
, Just Entities <$ switch (long "entities" <> help "Generate entities page (uses data from entities.yaml)")
135-
, Just Recipes <$ switch (long "recipes" <> help "Generate recipes page (uses data from recipes.yaml)")
136-
, Just Capabilities <$ switch (long "capabilities" <> help "Generate capabilities page (uses entity map)")
137-
, Just Commands <$ switch (long "commands" <> help "Generate commands page (uses constInfo, constCaps and inferConst)")
138-
, Just Scenario <$ switch (long "scenario" <> help "Generate scenario schema page")
139-
]
14095
seed :: Parser (Maybe Int)
14196
seed = optional $ option auto (long "seed" <> short 's' <> metavar "INT" <> help "Seed to use for world generation")
14297
webPort :: Parser (Maybe Int)
@@ -218,7 +173,6 @@ main = do
218173
cli <- execParser cliInfo
219174
case cli of
220175
Run opts -> appMain opts
221-
DocGen g -> generateDocs g
222176
Format fo w -> formatFile fo w
223177
RenderMap mapPath opts -> doRenderCmd opts mapPath
224178
LSP -> lspMain

app/doc/Main.hs

+66
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,66 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
3+
-- |
4+
-- SPDX-License-Identifier: BSD-3-Clause
5+
module Main where
6+
7+
import Data.Foldable qualified
8+
import Data.Maybe (fromMaybe)
9+
import Data.Text qualified as T
10+
import Options.Applicative
11+
import Swarm.Doc.Gen (GenerateDocs (..), PageAddress (..), SheetType (..), generateDocs)
12+
import Swarm.Doc.Keyword (EditorType (..))
13+
14+
cliParser :: Parser GenerateDocs
15+
cliParser =
16+
subparser $
17+
mconcat
18+
[ command "recipes" (info (pure RecipeGraph) $ progDesc "Output graphviz dotfile of entity dependencies based on recipes")
19+
, command "editors" (info (EditorKeywords <$> editor <**> helper) $ progDesc "Output editor keywords")
20+
, command "keys" (info (pure SpecialKeyNames) $ progDesc "Output list of recognized special key names")
21+
, command "cheatsheet" (info (CheatSheet <$> address <*> cheatsheet <**> helper) $ progDesc "Output nice Wiki tables")
22+
, command "pedagogy" (info (pure TutorialCoverage) $ progDesc "Output tutorial coverage")
23+
, command "endpoints" (info (pure WebAPIEndpoints) $ progDesc "Generate markdown Web API documentation.")
24+
]
25+
where
26+
editor :: Parser (Maybe EditorType)
27+
editor =
28+
Data.Foldable.asum
29+
[ pure Nothing
30+
, Just VSCode <$ switch (long "code" <> help "Generate for the VS Code editor")
31+
, Just Emacs <$ switch (long "emacs" <> help "Generate for the Emacs editor")
32+
]
33+
address :: Parser PageAddress
34+
address =
35+
let replace a b = T.unpack . T.replace a b . T.pack
36+
opt n =
37+
fmap (fromMaybe "") . optional $
38+
option
39+
str
40+
( long n
41+
<> metavar "ADDRESS"
42+
<> help ("Set the address of " <> replace "-" " " n <> ". Default no link.")
43+
)
44+
in PageAddress <$> opt "entities-page" <*> opt "commands-page" <*> opt "capabilities-page" <*> opt "recipes-page"
45+
cheatsheet :: Parser (Maybe SheetType)
46+
cheatsheet =
47+
Data.Foldable.asum
48+
[ pure Nothing
49+
, Just Entities <$ switch (long "entities" <> help "Generate entities page (uses data from entities.yaml)")
50+
, Just Recipes <$ switch (long "recipes" <> help "Generate recipes page (uses data from recipes.yaml)")
51+
, Just Capabilities <$ switch (long "capabilities" <> help "Generate capabilities page (uses entity map)")
52+
, Just Commands <$ switch (long "commands" <> help "Generate commands page (uses constInfo, constCaps and inferConst)")
53+
, Just Scenario <$ switch (long "scenario" <> help "Generate scenario schema page")
54+
]
55+
56+
cliInfo :: ParserInfo GenerateDocs
57+
cliInfo =
58+
info
59+
(cliParser <**> helper)
60+
( header "Swarm docs"
61+
<> progDesc "Generate swarm documentation."
62+
<> fullDesc
63+
)
64+
65+
main :: IO ()
66+
main = generateDocs =<< execParser cliInfo

src/Swarm/Doc/Gen.hs renamed to app/doc/Swarm/Doc/Gen.hs

+3-43
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE LambdaCase #-}
23
{-# LANGUAGE OverloadedStrings #-}
34

45
-- |
@@ -9,15 +10,7 @@ module Swarm.Doc.Gen (
910
-- ** Main document generation function + types
1011
generateDocs,
1112
GenerateDocs (..),
12-
EditorType (..),
1313
SheetType (..),
14-
loadStandaloneScenario,
15-
16-
-- ** Formatted keyword lists
17-
keywordsCommands,
18-
keywordsDirections,
19-
operatorNames,
20-
builtinFunctionList,
2114

2215
-- ** Wiki pages
2316
PageAddress (..),
@@ -36,6 +29,7 @@ import Data.Text (Text, unpack)
3629
import Data.Text qualified as T
3730
import Data.Text.IO qualified as T
3831
import Data.Tuple (swap)
32+
import Swarm.Doc.Keyword
3933
import Swarm.Doc.Pedagogy
4034
import Swarm.Doc.Util
4135
import Swarm.Doc.Wiki.Cheatsheet
@@ -47,8 +41,7 @@ import Swarm.Game.Scenario (loadStandaloneScenario)
4741
import Swarm.Game.World.Gen (extractEntities)
4842
import Swarm.Game.World.Typecheck (Some (..), TTerm)
4943
import Swarm.Language.Key (specialKeyNames)
50-
import Swarm.Language.Syntax qualified as Syntax
51-
import Swarm.Util (both, listEnums, quote)
44+
import Swarm.Util (both, listEnums)
5245
import Swarm.Util.Effect (simpleErrorHandle)
5346
import Swarm.Web (swarmApiMarkdown)
5447
import Text.Dot (Dot, NodeId, (.->.))
@@ -78,11 +71,6 @@ data GenerateDocs where
7871
WebAPIEndpoints :: GenerateDocs
7972
deriving (Eq, Show)
8073

81-
-- | An enumeration of the editors supported by Swarm (currently,
82-
-- Emacs and VS Code).
83-
data EditorType = Emacs | VSCode | Vim
84-
deriving (Eq, Show, Enum, Bounded)
85-
8674
-- | Generate the requested kind of documentation to stdout.
8775
generateDocs :: GenerateDocs -> IO ()
8876
generateDocs = \case
@@ -133,34 +121,6 @@ generateEditorKeywords = \case
133121
putStr "\nsyn keyword Direction "
134122
T.putStrLn $ keywordsDirections Vim
135123

136-
builtinFunctionList :: EditorType -> Text
137-
builtinFunctionList e = editorList e $ map constSyntax builtinFunctions
138-
139-
editorList :: EditorType -> [Text] -> Text
140-
editorList = \case
141-
Emacs -> T.unlines . map ((" " <>) . quote)
142-
VSCode -> T.intercalate "|"
143-
Vim -> T.intercalate " "
144-
145-
-- | Get formatted list of basic functions/commands.
146-
keywordsCommands :: EditorType -> Text
147-
keywordsCommands e = editorList e $ map constSyntax commands
148-
149-
-- | Get formatted list of directions.
150-
keywordsDirections :: EditorType -> Text
151-
keywordsDirections e = editorList e $ map Syntax.directionSyntax Syntax.allDirs
152-
153-
-- | A list of the names of all the operators in the language.
154-
operatorNames :: Text
155-
operatorNames = T.intercalate "|" $ map (escape . constSyntax) operators
156-
where
157-
special :: String
158-
special = "*+$[]|^"
159-
slashNotComment = \case
160-
'/' -> "/(?![/|*])"
161-
c -> T.singleton c
162-
escape = T.concatMap (\c -> if c `elem` special then T.snoc "\\\\" c else slashNotComment c)
163-
164124
-- ----------------------------------------------------------------------------
165125
-- GENERATE SPECIAL KEY NAMES
166126
-- ----------------------------------------------------------------------------
File renamed without changes.

src/Swarm/Doc/Schema/Refined.hs renamed to app/doc/Swarm/Doc/Schema/Refined.hs

+1
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE LambdaCase #-}
12
{-# LANGUAGE OverloadedStrings #-}
23

34
-- |

src/Swarm/Doc/Schema/Render.hs renamed to app/doc/Swarm/Doc/Schema/Render.hs

+1
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE LambdaCase #-}
12
{-# LANGUAGE OverloadedStrings #-}
23

34
-- |

editors/emacs/swarm-mode.el

+1-1
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@
2626
(setq swarm-font-lock-keywords
2727
(let* (
2828
;; Generate the current keywords with:
29-
;; cabal run swarm:swarm -- generate editors --emacs
29+
;; cabal run swarm:swarm-docs -- editors --emacs
3030
(x-keywords '("def" "end" "let" "in" "require"))
3131
(x-builtins '(
3232
"self"

editors/vscode/DEVELOPING.md

+3-3
Original file line numberDiff line numberDiff line change
@@ -28,11 +28,11 @@
2828

2929
### Updating the syntax highlighting
3030

31-
Whenever swarm language adds new features, the highlighing needs to be updated.
31+
Whenever swarm language adds new features, the highlighting needs to be updated.
3232

33-
To save some time, get the current reserved words by running `swarm generate`:
33+
To save some time, get the current reserved words by running `swarm-docs`:
3434
```bash
35-
cabal run swarm:swarm -- generate editors
35+
cabal run swarm:swarm-docs -- editors
3636
```
3737

3838
You still have to add for example types manually.

src/Swarm/Doc/Keyword.hs

+55
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,55 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
4+
-- |
5+
-- SPDX-License-Identifier: BSD-3-Clause
6+
--
7+
-- Collect keywords for documentation generation and testing.
8+
module Swarm.Doc.Keyword (
9+
EditorType (..),
10+
11+
-- ** Formatted keyword lists
12+
keywordsCommands,
13+
keywordsDirections,
14+
operatorNames,
15+
builtinFunctionList,
16+
) where
17+
18+
import Data.Text (Text)
19+
import Data.Text qualified as T
20+
import Swarm.Doc.Util
21+
import Swarm.Language.Syntax qualified as Syntax
22+
import Swarm.Util (quote)
23+
24+
-- | An enumeration of the editors supported by Swarm (currently,
25+
-- Emacs and VS Code).
26+
data EditorType = Emacs | VSCode | Vim
27+
deriving (Eq, Show, Enum, Bounded)
28+
29+
builtinFunctionList :: EditorType -> Text
30+
builtinFunctionList e = editorList e $ map constSyntax builtinFunctions
31+
32+
editorList :: EditorType -> [Text] -> Text
33+
editorList = \case
34+
Emacs -> T.unlines . map ((" " <>) . quote)
35+
VSCode -> T.intercalate "|"
36+
Vim -> T.intercalate " "
37+
38+
-- | Get formatted list of basic functions/commands.
39+
keywordsCommands :: EditorType -> Text
40+
keywordsCommands e = editorList e $ map constSyntax commands
41+
42+
-- | Get formatted list of directions.
43+
keywordsDirections :: EditorType -> Text
44+
keywordsDirections e = editorList e $ map Syntax.directionSyntax Syntax.allDirs
45+
46+
-- | A list of the names of all the operators in the language.
47+
operatorNames :: Text
48+
operatorNames = T.intercalate "|" $ map (escape . constSyntax) operators
49+
where
50+
special :: String
51+
special = "*+$[]|^"
52+
slashNotComment = \case
53+
'/' -> "/(?![/|*])"
54+
c -> T.singleton c
55+
escape = T.concatMap (\c -> if c `elem` special then T.snoc "\\\\" c else slashNotComment c)

src/Swarm/Game/World/Render.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -17,13 +17,12 @@ import Data.Tuple.Extra (both)
1717
import Data.Vector qualified as V
1818
import Graphics.Vty.Attributes.Color240
1919
import Linear (V2 (..))
20-
import Swarm.Doc.Gen (loadStandaloneScenario)
2120
import Swarm.Game.Display (Attribute (AWorld), defaultChar, displayAttr)
2221
import Swarm.Game.Entity.Cosmetic
2322
import Swarm.Game.Entity.Cosmetic.Assignment (terrainAttributes)
2423
import Swarm.Game.Location
2524
import Swarm.Game.ResourceLoading (initNameGenerator, readAppData)
26-
import Swarm.Game.Scenario (Scenario, area, scenarioCosmetics, scenarioWorlds, ul, worldName)
25+
import Swarm.Game.Scenario (Scenario, area, loadStandaloneScenario, scenarioCosmetics, scenarioWorlds, ul, worldName)
2726
import Swarm.Game.Scenario.Status (seedLaunchParams)
2827
import Swarm.Game.Scenario.Topography.Area (AreaDimensions (..), getAreaDimensions, isEmpty, upperLeftToBottomRight)
2928
import Swarm.Game.Scenario.Topography.Cell

0 commit comments

Comments
 (0)