{-# LANGUAGE OverloadedStrings #-}
module Swarm.Doc.Util where
import Control.Effect.Throw (Has, Throw, throwError)
import Control.Lens (view)
import Data.Maybe (listToMaybe)
import Data.Text (Text)
import Data.Text qualified as T
import Swarm.Game.Failure (SystemFailure (CustomFailure))
import Swarm.Game.Robot (Robot)
import Swarm.Game.Robot.Concrete (instantiateRobot)
import Swarm.Game.Scenario (ScenarioLandscape, scenarioRobots)
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
instantiateBaseRobot :: Has (Throw SystemFailure) sig m => ScenarioLandscape -> m Robot
instantiateBaseRobot :: forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
Has (Throw SystemFailure) sig m =>
ScenarioLandscape -> m Robot
instantiateBaseRobot ScenarioLandscape
sLandscape = case [TRobot] -> Maybe TRobot
forall a. [a] -> Maybe a
listToMaybe ([TRobot] -> Maybe TRobot) -> [TRobot] -> Maybe TRobot
forall a b. (a -> b) -> a -> b
$ Getting [TRobot] ScenarioLandscape [TRobot]
-> ScenarioLandscape -> [TRobot]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting [TRobot] ScenarioLandscape [TRobot]
Lens' ScenarioLandscape [TRobot]
scenarioRobots ScenarioLandscape
sLandscape of
Just TRobot
r -> Robot -> m Robot
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Robot -> m Robot) -> Robot -> m Robot
forall a b. (a -> b) -> a -> b
$ Maybe CESK -> RID -> TRobot -> Robot
instantiateRobot Maybe CESK
forall a. Maybe a
Nothing RID
0 TRobot
r
Maybe TRobot
Nothing -> SystemFailure -> m Robot
forall e (sig :: (* -> *) -> * -> *) (m :: * -> *) a.
Has (Throw e) sig m =>
e -> m a
throwError (SystemFailure -> m Robot) -> SystemFailure -> m Robot
forall a b. (a -> b) -> a -> b
$ Text -> SystemFailure
CustomFailure Text
"Scenario contains no robots"