{-# LANGUAGE OverloadedStrings #-}
module Swarm.Doc.Util where
import Data.Text (Text)
import Data.Text qualified as T
import Swarm.Language.Syntax (Const (..))
import Swarm.Language.Syntax qualified as Syntax
wrap :: Char -> Text -> Text
wrap :: Char -> Text -> Text
wrap Char
c = Char -> Text -> Text
T.cons Char
c (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Char -> Text) -> Char -> Text -> Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Char -> Text
T.snoc Char
c
codeQuote :: Text -> Text
codeQuote :: Text -> Text
codeQuote = Char -> Text -> Text
wrap Char
'`'
addLink :: Text -> Text -> Text
addLink :: Text -> Text -> Text
addLink Text
l Text
t = [Text] -> Text
T.concat [Text
"[", Text
t, Text
"](", Text
l, Text
")"]
operators :: [Const]
operators :: [Const]
operators = (Const -> Bool) -> [Const] -> [Const]
forall a. (a -> Bool) -> [a] -> [a]
filter Const -> Bool
Syntax.isOperator [Const]
Syntax.allConst
builtinFunctions :: [Const]
builtinFunctions :: [Const]
builtinFunctions = (Const -> Bool) -> [Const] -> [Const]
forall a. (a -> Bool) -> [a] -> [a]
filter Const -> Bool
Syntax.isBuiltinFunction [Const]
Syntax.allConst
commands :: [Const]
commands :: [Const]
commands = (Const -> Bool) -> [Const] -> [Const]
forall a. (a -> Bool) -> [a] -> [a]
filter Const -> Bool
Syntax.isCmd [Const]
Syntax.allConst
constSyntax :: Const -> Text
constSyntax :: Const -> Text
constSyntax = ConstInfo -> Text
Syntax.syntax (ConstInfo -> Text) -> (Const -> ConstInfo) -> Const -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Const -> ConstInfo
Syntax.constInfo