License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Game.ScenarioInfo
Description
Saving and loading info about scenarios (status, path, etc.) as well as loading recursive scenario collections.
Synopsis
- data ScenarioStatus
- _NotStarted :: Prism' ScenarioStatus ()
- type ScenarioInfo = ScenarioInfoT FilePath
- scenarioPath :: Lens' ScenarioInfo FilePath
- scenarioStatus :: Lens' ScenarioInfo ScenarioStatus
- data CodeSizeDeterminators = CodeSizeDeterminators (Maybe Syntax) Bool
- data ScenarioWith a
- newtype ScenarioCollection a = SC {
- scMap :: OMap FilePath (ScenarioItem a)
- scenarioCollectionToList :: ScenarioCollection a -> [ScenarioItem a]
- flatten :: ScenarioItem a -> [ScenarioWith a]
- scenarioItemByPath :: FilePath -> Traversal' (ScenarioCollection a) (ScenarioItem a)
- normalizeScenarioPath :: MonadIO m => ScenarioCollection a -> FilePath -> m FilePath
- data ScenarioItem a
- = SISingle (ScenarioWith a)
- | SICollection Text (ScenarioCollection a)
- scenarioItemName :: ScenarioItem a -> Text
- _SISingle :: forall a p f. (Choice p, Applicative f) => p (ScenarioWith a) (f (ScenarioWith a)) -> p (ScenarioItem a) (f (ScenarioItem a))
- pathifyCollection :: Functor f => f ScenarioInfo -> f ScenarioPath
- tutorialsDirname :: FilePath
- getTutorials :: ScenarioCollection a -> ScenarioCollection a
- loadScenarios :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Accum (Seq SystemFailure)) sig m, Has (Lift IO) sig m) => ScenarioInputs -> Bool -> m (ScenarioCollection ScenarioInfo)
- loadScenarioInfo :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => FilePath -> m ScenarioInfo
- saveScenarioInfo :: FilePath -> ScenarioInfo -> IO ()
Scenario info
data ScenarioStatus Source #
A ScenarioStatus
stores the status of a scenario along with
appropriate metadata: NotStarted
, or Played
.
The Played
status has two sub-states: Attempted
or Completed
.
Instances
_NotStarted :: Prism' ScenarioStatus () Source #
type ScenarioInfo = ScenarioInfoT FilePath Source #
scenarioPath :: Lens' ScenarioInfo FilePath Source #
The path of the scenario, relative to data/scenarios
.
scenarioStatus :: Lens' ScenarioInfo ScenarioStatus Source #
The status of the scenario.
data CodeSizeDeterminators Source #
Constructors
CodeSizeDeterminators (Maybe Syntax) Bool |
Instances
Show CodeSizeDeterminators Source # | |
Defined in Swarm.Game.Scenario.Scoring.CodeSize Methods showsPrec :: Int -> CodeSizeDeterminators -> ShowS # show :: CodeSizeDeterminators -> String # showList :: [CodeSizeDeterminators] -> ShowS # |
data ScenarioWith a Source #
Instances
Functor ScenarioWith Source # | |||||
Defined in Swarm.Game.Scenario.Status Methods fmap :: (a -> b) -> ScenarioWith a -> ScenarioWith b # (<$) :: a -> ScenarioWith b -> ScenarioWith a # | |||||
Generic (ScenarioWith a) Source # | |||||
Defined in Swarm.Game.Scenario.Status Associated Types
Methods from :: ScenarioWith a -> Rep (ScenarioWith a) x # to :: Rep (ScenarioWith a) x -> ScenarioWith a # | |||||
type Rep (ScenarioWith a) Source # | |||||
Defined in Swarm.Game.Scenario.Status type Rep (ScenarioWith a) = D1 ('MetaData "ScenarioWith" "Swarm.Game.Scenario.Status" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-engine" 'False) (C1 ('MetaCons "ScenarioWith" 'PrefixI 'True) (S1 ('MetaSel ('Just "_getScenario") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scenario) :*: S1 ('MetaSel ('Just "_getScenarioInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) |
Scenario collection
newtype ScenarioCollection a Source #
A scenario collection is a tree of scenarios, keyed by name, together with an optional order.
Invariant: every item in the
scOrder
exists as a key in the scMap
.
Constructors
SC | |
Fields
|
Instances
Functor ScenarioCollection Source # | |
Defined in Swarm.Game.ScenarioInfo Methods fmap :: (a -> b) -> ScenarioCollection a -> ScenarioCollection b # (<$) :: a -> ScenarioCollection b -> ScenarioCollection a # |
scenarioCollectionToList :: ScenarioCollection a -> [ScenarioItem a] Source #
Convert a scenario collection to a list of scenario items.
flatten :: ScenarioItem a -> [ScenarioWith a] Source #
scenarioItemByPath :: FilePath -> Traversal' (ScenarioCollection a) (ScenarioItem a) Source #
Access and modify ScenarioItem
s in collection based on their path.
normalizeScenarioPath :: MonadIO m => ScenarioCollection a -> FilePath -> m FilePath Source #
Canonicalize a scenario path, making it usable as a unique key.
data ScenarioItem a Source #
A scenario item is either a specific scenario, or a collection of scenarios (e.g. the scenarios contained in a subdirectory).
Constructors
SISingle (ScenarioWith a) | |
SICollection Text (ScenarioCollection a) |
Instances
Functor ScenarioItem Source # | |
Defined in Swarm.Game.ScenarioInfo Methods fmap :: (a -> b) -> ScenarioItem a -> ScenarioItem b # (<$) :: a -> ScenarioItem b -> ScenarioItem a # |
scenarioItemName :: ScenarioItem a -> Text Source #
Retrieve the name of a scenario item.
_SISingle :: forall a p f. (Choice p, Applicative f) => p (ScenarioWith a) (f (ScenarioWith a)) -> p (ScenarioItem a) (f (ScenarioItem a)) Source #
pathifyCollection :: Functor f => f ScenarioInfo -> f ScenarioPath Source #
Tutorials
tutorialsDirname :: FilePath Source #
Subdirectory of the scenarios directory where tutorials are stored.
getTutorials :: ScenarioCollection a -> ScenarioCollection a Source #
Extract just the collection of tutorial scenarios from the entire scenario collection.
Loading and saving scenarios
loadScenarios :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Accum (Seq SystemFailure)) sig m, Has (Lift IO) sig m) => ScenarioInputs -> Bool -> m (ScenarioCollection ScenarioInfo) Source #
Load all the scenarios from the scenarios data directory.
loadScenarioInfo :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => FilePath -> m ScenarioInfo Source #
Load saved info about played scenario from XDG data directory.
saveScenarioInfo :: FilePath -> ScenarioInfo -> IO () Source #
Save info about played scenario to XDG data directory.