swarm-0.2.0.0: 2D resource gathering game with programmable robots
CopyrightBrent Yorgey
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Language.Pipeline

Description

Some convenient functions for putting together the whole Swarm language processing pipeline: parsing, type checking, capability checking, and elaboration. If you want to simply turn some raw text representing a Swarm program into something useful, this is probably the module you want.

Synopsis

Documentation

data ProcessedTerm Source #

A record containing the results of the language processing pipeline. Put a Term in, and get one of these out.

Constructors

ProcessedTerm 

Fields

  • Term

    The elaborated term

  • TModule

    The type of the term (and of any embedded definitions)

  • Requirements

    Requirements of the term

  • ReqCtx

    Capability context for any definitions embedded in the term

Instances

Instances details
FromJSON ProcessedTerm Source # 
Instance details

Defined in Swarm.Language.Pipeline

ToJSON ProcessedTerm Source # 
Instance details

Defined in Swarm.Language.Pipeline

Data ProcessedTerm Source # 
Instance details

Defined in Swarm.Language.Pipeline

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProcessedTerm -> c ProcessedTerm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProcessedTerm #

toConstr :: ProcessedTerm -> Constr #

dataTypeOf :: ProcessedTerm -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProcessedTerm) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProcessedTerm) #

gmapT :: (forall b. Data b => b -> b) -> ProcessedTerm -> ProcessedTerm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProcessedTerm -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProcessedTerm -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProcessedTerm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProcessedTerm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProcessedTerm -> m ProcessedTerm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProcessedTerm -> m ProcessedTerm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProcessedTerm -> m ProcessedTerm #

Generic ProcessedTerm Source # 
Instance details

Defined in Swarm.Language.Pipeline

Associated Types

type Rep ProcessedTerm :: Type -> Type #

Show ProcessedTerm Source # 
Instance details

Defined in Swarm.Language.Pipeline

Eq ProcessedTerm Source # 
Instance details

Defined in Swarm.Language.Pipeline

type Rep ProcessedTerm Source # 
Instance details

Defined in Swarm.Language.Pipeline

processTerm :: Text -> Either Text (Maybe ProcessedTerm) Source #

Given a Text value representing a Swarm program,

  1. Parse it (see Swarm.Language.Parse)
  2. Typecheck it (see Swarm.Language.Typecheck)
  3. Elaborate it (see Swarm.Language.Elaborate)
  4. Check what capabilities it requires (see Swarm.Language.Capability)

Return either the end result (or Nothing if the input was only whitespace) or a pretty-printed error message.

processParsedTerm :: Syntax -> Either TypeErr ProcessedTerm Source #

Like processTerm, but use a term that has already been parsed.

processTerm' :: TCtx -> ReqCtx -> Text -> Either Text (Maybe ProcessedTerm) Source #

Like processTerm, but use explicit starting contexts.

processParsedTerm' :: TCtx -> ReqCtx -> Syntax -> Either TypeErr ProcessedTerm Source #

Like processTerm', but use a term that has already been parsed.