swarm-0.7.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellNone
LanguageHaskell2010

Swarm.Language.Syntax

Description

Abstract syntax for terms of the Swarm programming language.

Synopsis

Constants

data Const Source #

Constants, representing various built-in functions and commands.

IF YOU ADD A NEW CONSTANT, be sure to also update: 1. the constInfo function (below) 2. the capability checker (Swarm.Language.Capability) 3. the type checker (Swarm.Language.Typecheck) 4. the runtime (Swarm.Game.Step) 5. the emacs mode syntax highlighter (contribs/swarm-mode.el)

GHC will warn you about incomplete pattern matches for the first four, and CI will warn you about the last, so in theory it's not really possible to forget. Note you do not need to update the parser or pretty-printer, since they are auto-generated from constInfo.

Constructors

Noop

Do nothing. This is different than Wait in that it does not take up a time step.

Wait

Wait for a number of time steps without doing anything.

Selfdestruct

Self-destruct.

Move

Move forward one step.

Backup

Move backward one step.

Volume

Measure the size of the enclosed volume

Path

Describe a path to the destination.

Push

Push an entity forward one step.

Stride

Move forward multiple steps.

Turn

Turn in some direction.

Grab

Grab an item from the current location.

Harvest

Harvest an item from the current location.

Sow

Scatter seeds of a plant

Ignite

Ignite a combustible item

Place

Try to place an item at the current location.

Ping

Obtain the relative location of another robot.

Give

Give an item to another robot at the current location.

Equip

Equip a device on oneself.

Unequip

Unequip an equipped device, returning to inventory.

Make

Make an item.

Has

Sense whether we have a certain item.

Equipped

Sense whether we have a certain device equipped.

Count

Sense how many of a certain item we have.

Drill

Drill through an entity.

Use

Use an entity with another.

Build

Construct a new robot.

Salvage

Deconstruct an old robot.

Reprogram

Reprogram a robot that has executed it's command with a new command

Say

Emit a message.

Listen

Listen for a message from other robots.

Log

Emit a log message.

View

View a certain robot.

Appear

Set color and what characters are used for display.

Create

Create an entity out of thin air. Only available in creative mode.

Halt

Tell a robot to halt.

Time

Get current time

Scout 
Whereami

Get the current x, y coordinates

LocateMe

Get the current subworld and x, y coordinates

Waypoints

Get the list of x, y coordinates of the waypoints for a given name

Structures

Get the list of x, y coordinates of the southwest corner of all constructed structures of a given name

Floorplan

Get the width and height of a structure template

HasTag

Answer whether a given entity has the given tag

TagMembers

Get the list of entity names that are labeled with a given tag

Detect

Locate the closest instance of a given entity within the rectangle specified by opposite corners, relative to the current location.

Resonate

Count the number of a given entity within the rectangle specified by opposite corners, relative to the current location.

Density

Count the number entities within the rectangle specified by opposite corners, relative to the current location.

Sniff

Get the distance to the closest instance of the specified entity.

Chirp

Get the direction to the closest instance of the specified entity.

Watch

Register a location to interrupt a wait upon changes

Surveil

Register a (remote) location to interrupt a wait upon changes

Heading

Get the current heading.

Blocked

See if we can move forward or not.

Scan

Scan a nearby cell

Upload

Upload knowledge to another robot

Ishere

See if a specific entity is here.

Isempty

Check whether the current cell is empty

Self

Get a reference to oneself

Parent

Get the robot's parent

Base

Get a reference to the base

Meet

Meet a nearby robot

MeetAll

Meet all nearby robots

Whoami

Get the robot's display name

Setname

Set the robot's display name

Random

Get a uniformly random integer.

Run

Run a program loaded from a file.

If

If-expressions.

Inl

Left injection.

Inr

Right injection.

Case

Case analysis on a sum type.

Match

Pair eliminator.

Force

Force a delayed evaluation.

Pure

Pure for the cmd monad.

Try

Try/catch block

Undefined

Undefined

Fail

User error

Not

Logical negation.

Neg

Arithmetic negation.

Eq

Logical equality comparison

Neq

Logical inequality comparison

Lt

Logical lesser-then comparison

Gt

Logical greater-then comparison

Leq

Logical lesser-or-equal comparison

Geq

Logical greater-or-equal comparison

Or

Logical or.

And

Logical and.

Add

Arithmetic addition operator

Sub

Arithmetic subtraction operator

Mul

Arithmetic multiplication operator

Div

Arithmetic division operator

Exp

Arithmetic exponentiation operator

Format

Turn an arbitrary value into a string

Read

Try to turn a string into a value

Print

Print a string onto a printable surface

Erase

Erase a printable surface

Concat

Concatenate string values

Chars

Count number of characters.

Split

Split string into two parts.

CharAt

Get the character at an index.

ToChar

Create a singleton text value with the given character code.

AppF

Application operator - helps to avoid parentheses: f $ g $ h x = f (g (h x))

Swap

Swap placed entity with one in inventory. Essentially atomic grab and place.

Atomic

When executing atomic c, a robot will not be interrupted, that is, no other robots will execute any commands while the robot is executing c.

Instant

Like atomic, but with no restriction on program size.

Key

Create key values.

InstallKeyHandler

Install a new keyboard input handler.

Teleport

Teleport a robot to the given position.

Warp

Relocate a robot to the given cosmic position.

As

Run a command as if you were another robot.

RobotNamed

Find an actor by name.

RobotNumbered

Find an actor by number.

Knows

Check if an entity is known.

Instances

Instances details
FromJSON Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

FromJSONKey Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

ToJSON Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

ToJSONKey Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Data Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

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

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

toConstr :: Const -> Constr #

dataTypeOf :: Const -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Enum Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Generic Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Associated Types

type Rep Const 
Instance details

Defined in Swarm.Language.Syntax.Constants

type Rep Const = D1 ('MetaData "Const" "Swarm.Language.Syntax.Constants" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) ((((((C1 ('MetaCons "Noop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Wait" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Selfdestruct" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Move" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Backup" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Volume" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Path" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Push" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Stride" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Turn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Grab" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Harvest" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ignite" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Place" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Give" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Equip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unequip" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Make" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Has" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Equipped" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Count" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Drill" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Use" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Build" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Salvage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reprogram" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Say" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Listen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Log" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "View" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Appear" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Create" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Halt" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Time" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Scout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Whereami" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LocateMe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Waypoints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Structures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Floorplan" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HasTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TagMembers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Detect" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Resonate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Density" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sniff" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Chirp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Watch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Surveil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Heading" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Blocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Scan" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Upload" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ishere" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Isempty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Self" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Parent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Base" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Meet" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MeetAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Whoami" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Setname" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Random" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Run" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "If" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Inl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Inr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Case" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Match" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Force" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pure" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Try" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Undefined" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fail" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Not" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Neg" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Eq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Neq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Lt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Leq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Geq" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mul" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Div" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Format" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Read" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Print" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Erase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Concat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Chars" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Split" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CharAt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ToChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppF" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Swap" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atomic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Instant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Key" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "InstallKeyHandler" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Teleport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Warp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "As" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RobotNamed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RobotNumbered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Knows" 'PrefixI 'False) (U1 :: Type -> Type))))))))

Methods

from :: Const -> Rep Const x #

to :: Rep Const x -> Const #

Show Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

showsPrec :: Int -> Const -> ShowS #

show :: Const -> String #

showList :: [Const] -> ShowS #

Eq Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

(==) :: Const -> Const -> Bool #

(/=) :: Const -> Const -> Bool #

Ord Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

compare :: Const -> Const -> Ordering #

(<) :: Const -> Const -> Bool #

(<=) :: Const -> Const -> Bool #

(>) :: Const -> Const -> Bool #

(>=) :: Const -> Const -> Bool #

max :: Const -> Const -> Const #

min :: Const -> Const -> Const #

Hashable Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

hashWithSalt :: Int -> Const -> Int #

hash :: Const -> Int #

PrettyPrec Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

prettyPrec :: Int -> Const -> Doc ann

type Rep Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

type Rep Const = D1 ('MetaData "Const" "Swarm.Language.Syntax.Constants" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) ((((((C1 ('MetaCons "Noop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Wait" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Selfdestruct" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Move" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Backup" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Volume" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Path" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Push" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Stride" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Turn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Grab" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Harvest" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ignite" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Place" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Give" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Equip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unequip" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Make" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Has" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Equipped" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Count" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Drill" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Use" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Build" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Salvage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reprogram" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Say" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Listen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Log" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "View" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Appear" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Create" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Halt" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Time" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Scout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Whereami" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LocateMe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Waypoints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Structures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Floorplan" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HasTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TagMembers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Detect" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Resonate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Density" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sniff" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Chirp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Watch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Surveil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Heading" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Blocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Scan" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Upload" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ishere" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Isempty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Self" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Parent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Base" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Meet" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MeetAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Whoami" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Setname" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Random" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Run" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "If" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Inl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Inr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Case" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Match" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Force" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pure" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Try" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Undefined" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fail" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Not" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Neg" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Eq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Neq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Lt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Leq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Geq" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mul" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Div" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Format" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Read" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Print" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Erase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Concat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Chars" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Split" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CharAt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ToChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppF" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Swap" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atomic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Instant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Key" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "InstallKeyHandler" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Teleport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Warp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "As" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RobotNamed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RobotNumbered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Knows" 'PrefixI 'False) (U1 :: Type -> Type))))))))

data ConstDoc Source #

Constructors

ConstDoc 

Fields

data ConstMeta Source #

Constructors

ConstMFunc

Function with arity of which some are commands

Fields

ConstMUnOp MUnAssoc

Unary operator with fixity and associativity.

ConstMBinOp MBinAssoc

Binary operator with fixity and associativity.

data MBinAssoc Source #

The meta type representing associativity of binary operator.

Constructors

L

Left associative binary operator (see InfixL)

N

Non-associative binary operator (see InfixN)

R

Right associative binary operator (see InfixR)

data MUnAssoc Source #

The meta type representing associativity of unary operator.

Constructors

P

Prefix unary operator (see Prefix)

S

Suffix unary operator (see Suffix)

constInfo :: Const -> ConstInfo Source #

Information about constants used in parsing and pretty printing.

It would be more compact to represent the information by testing whether the constants are in certain sets, but using pattern matching gives us warning if we add more constants.

arity :: Const -> Int Source #

The arity of a constant, i.e. how many arguments it expects. The runtime system will collect arguments to a constant (see VCApp) until it has enough, then dispatch the constant's behavior.

isCmd :: Const -> Bool Source #

Whether a constant represents a command. Constants which are not commands are functions which are interpreted as soon as they are evaluated. Commands, on the other hand, are not interpreted until being executed, that is, when meeting an FExec frame. When evaluated, commands simply turn into a VCApp.

isUserFunc :: Const -> Bool Source #

Function constants user can call with reserved words (wait,...).

isOperator :: Const -> Bool Source #

Whether the constant is an operator. Useful predicate for documentation.

isBuiltinFunction :: Const -> Bool Source #

Whether the constant is a function which is interpreted as soon as it is evaluated, but *not* including operators.

Note: This is used for documentation purposes and complements isCmd and isOperator in that exactly one will accept a given constant.

isTangible :: Const -> Bool Source #

Whether the constant is a tangible command, that has an external effect on the world. At most one tangible command may be executed per tick.

isLong :: Const -> Bool Source #

Whether the constant is a long command, that is, a tangible command which could require multiple ticks to execute. Such commands cannot be allowed in atomic blocks.

Size limits

maxSniffRange :: Int32 Source #

Maximum perception distance for Chirp and Sniff commands

globalMaxVolume :: Integer Source #

Checked upon invocation of the command, before flood fill computation, to ensure the search has a reasonable bound.

The user is warned in the failure message that there exists a global limit.

SrcLoc

data SrcLoc Source #

The location of something in the textual source code (recorded as an interval measured in terms of indices into the input stream).

Constructors

NoLoc 
SrcLoc Int Int

Half-open interval from start (inclusive) to end (exclusive)

Instances

Instances details
FromJSON SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

ToJSON SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Data SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

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

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

toConstr :: SrcLoc -> Constr #

dataTypeOf :: SrcLoc -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid SrcLoc Source #

mempty is a special value which means we have no location information.

Instance details

Defined in Swarm.Language.Syntax.Loc

Semigroup SrcLoc Source #

x <> y is the smallest SrcLoc that subsumes both x and y.

Instance details

Defined in Swarm.Language.Syntax.Loc

Generic SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Associated Types

type Rep SrcLoc 
Instance details

Defined in Swarm.Language.Syntax.Loc

type Rep SrcLoc = D1 ('MetaData "SrcLoc" "Swarm.Language.Syntax.Loc" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "NoLoc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SrcLoc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))

Methods

from :: SrcLoc -> Rep SrcLoc x #

to :: Rep SrcLoc x -> SrcLoc #

Show SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Eq SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

(==) :: SrcLoc -> SrcLoc -> Bool #

(/=) :: SrcLoc -> SrcLoc -> Bool #

Ord SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Hashable SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

hashWithSalt :: Int -> SrcLoc -> Int #

hash :: SrcLoc -> Int #

type Rep SrcLoc Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

type Rep SrcLoc = D1 ('MetaData "SrcLoc" "Swarm.Language.Syntax.Loc" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "NoLoc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SrcLoc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))

srcLocStartsBefore :: SrcLoc -> SrcLoc -> Bool Source #

Check whether one SrcLoc starts before another one, i.e. compare their starting indices to see if the first is <= the second.

srcLocEndsBefore :: SrcLoc -> SrcLoc -> Bool Source #

Check whether the first SrcLoc ends before the second, i.e. compare their ending indices to see if the first is <= the second.

Comments

data CommentType Source #

Line vs block comments.

Constructors

LineComment 
BlockComment 

Instances

Instances details
FromJSON CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

ToJSON CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Data CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

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

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

toConstr :: CommentType -> Constr #

dataTypeOf :: CommentType -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Enum CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Generic CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Associated Types

type Rep CommentType 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep CommentType = D1 ('MetaData "CommentType" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "LineComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockComment" 'PrefixI 'False) (U1 :: Type -> Type))
Read CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Show CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Eq CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Ord CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Hashable CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep CommentType Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep CommentType = D1 ('MetaData "CommentType" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "LineComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockComment" 'PrefixI 'False) (U1 :: Type -> Type))

data CommentSituation Source #

Was a comment all by itself on a line, or did it occur after some other tokens on a line?

Instances

Instances details
FromJSON CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

ToJSON CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Data CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

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

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

toConstr :: CommentSituation -> Constr #

dataTypeOf :: CommentSituation -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Enum CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Generic CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Associated Types

type Rep CommentSituation 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep CommentSituation = D1 ('MetaData "CommentSituation" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "StandaloneComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SuffixComment" 'PrefixI 'False) (U1 :: Type -> Type))
Read CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Show CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Eq CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Ord CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Hashable CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep CommentSituation Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep CommentSituation = D1 ('MetaData "CommentSituation" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "StandaloneComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SuffixComment" 'PrefixI 'False) (U1 :: Type -> Type))

isStandalone :: Comment -> Bool Source #

Test whether a comment is a standalone comment or not.

data Comment Source #

A comment is retained as some text plus metadata (source location, comment type, + comment situation). While parsing we record all comments out-of-band, for later re-insertion into the AST.

Instances

Instances details
FromJSON Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

ToJSON Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Data Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

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

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

toConstr :: Comment -> Constr #

dataTypeOf :: Comment -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Associated Types

type Rep Comment 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep Comment = D1 ('MetaData "Comment" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Comment" 'PrefixI 'True) ((S1 ('MetaSel ('Just "commentSrcLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SrcLoc) :*: S1 ('MetaSel ('Just "commentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentType)) :*: (S1 ('MetaSel ('Just "commentSituation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentSituation) :*: S1 ('MetaSel ('Just "commentText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))

Methods

from :: Comment -> Rep Comment x #

to :: Rep Comment x -> Comment #

Show Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Eq Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

(==) :: Comment -> Comment -> Bool #

(/=) :: Comment -> Comment -> Bool #

Hashable Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

hashWithSalt :: Int -> Comment -> Int #

hash :: Comment -> Int #

PrettyPrec Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

prettyPrec :: Int -> Comment -> Doc ann

type Rep Comment Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep Comment = D1 ('MetaData "Comment" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Comment" 'PrefixI 'True) ((S1 ('MetaSel ('Just "commentSrcLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SrcLoc) :*: S1 ('MetaSel ('Just "commentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentType)) :*: (S1 ('MetaSel ('Just "commentSituation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentSituation) :*: S1 ('MetaSel ('Just "commentText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))

data Comments Source #

Comments which can be attached to a particular AST node. Some comments come textually before the node and some come after.

Instances

Instances details
FromJSON Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

ToJSON Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Data Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

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

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

toConstr :: Comments -> Constr #

dataTypeOf :: Comments -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Semigroup Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Generic Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Associated Types

type Rep Comments 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep Comments = D1 ('MetaData "Comments" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Comments" 'PrefixI 'True) (S1 ('MetaSel ('Just "_beforeComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Comment)) :*: S1 ('MetaSel ('Just "_afterComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Comment))))

Methods

from :: Comments -> Rep Comments x #

to :: Rep Comments x -> Comments #

Show Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Eq Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Hashable Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

hashWithSalt :: Int -> Comments -> Int #

hash :: Comments -> Int #

AsEmpty Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

Methods

_Empty :: Prism' Comments () #

type Rep Comments Source # 
Instance details

Defined in Swarm.Language.Syntax.Comments

type Rep Comments = D1 ('MetaData "Comments" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Comments" 'PrefixI 'True) (S1 ('MetaSel ('Just "_beforeComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Comment)) :*: S1 ('MetaSel ('Just "_afterComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Comment))))

Syntax

data Syntax' ty Source #

The surface syntax for the language, with location and type annotations.

Constructors

Syntax' 

Fields

Instances

Instances details
FromJSON Syntax Source # 
Instance details

Defined in Swarm.Language.JSON

FromJSON TSyntax Source # 
Instance details

Defined in Swarm.Language.JSON

ToJSON Syntax Source # 
Instance details

Defined in Swarm.Language.JSON

ToJSON TSyntax Source # 
Instance details

Defined in Swarm.Language.JSON

Foldable Syntax' Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

fold :: Monoid m => Syntax' m -> m #

foldMap :: Monoid m => (a -> m) -> Syntax' a -> m #

foldMap' :: Monoid m => (a -> m) -> Syntax' a -> m #

foldr :: (a -> b -> b) -> b -> Syntax' a -> b #

foldr' :: (a -> b -> b) -> b -> Syntax' a -> b #

foldl :: (b -> a -> b) -> b -> Syntax' a -> b #

foldl' :: (b -> a -> b) -> b -> Syntax' a -> b #

foldr1 :: (a -> a -> a) -> Syntax' a -> a #

foldl1 :: (a -> a -> a) -> Syntax' a -> a #

toList :: Syntax' a -> [a] #

null :: Syntax' a -> Bool #

length :: Syntax' a -> Int #

elem :: Eq a => a -> Syntax' a -> Bool #

maximum :: Ord a => Syntax' a -> a #

minimum :: Ord a => Syntax' a -> a #

sum :: Num a => Syntax' a -> a #

product :: Num a => Syntax' a -> a #

Traversable Syntax' Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

traverse :: Applicative f => (a -> f b) -> Syntax' a -> f (Syntax' b) #

sequenceA :: Applicative f => Syntax' (f a) -> f (Syntax' a) #

mapM :: Monad m => (a -> m b) -> Syntax' a -> m (Syntax' b) #

sequence :: Monad m => Syntax' (m a) -> m (Syntax' a) #

Functor Syntax' Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

fmap :: (a -> b) -> Syntax' a -> Syntax' b #

(<$) :: a -> Syntax' b -> Syntax' a #

FromJSON (Document Syntax) Source # 
Instance details

Defined in Swarm.Language.Text.Markdown

ToJSON (Document Syntax) Source # 
Instance details

Defined in Swarm.Language.Text.Markdown

ToJSON (Paragraph Syntax) Source # 
Instance details

Defined in Swarm.Language.Text.Markdown

Data ty => Data (Syntax' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Syntax' ty -> c (Syntax' ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Syntax' ty) #

toConstr :: Syntax' ty -> Constr #

dataTypeOf :: Syntax' ty -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Syntax' ty -> Syntax' ty #

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

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

gmapQ :: (forall d. Data d => d -> u) -> Syntax' ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Syntax' ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Syntax' ty -> m (Syntax' ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Syntax' ty -> m (Syntax' ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Syntax' ty -> m (Syntax' ty) #

IsString (Document Syntax) Source # 
Instance details

Defined in Swarm.Language.Text.Markdown

IsString (Paragraph Syntax) Source # 
Instance details

Defined in Swarm.Language.Text.Markdown

Generic (Syntax' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Associated Types

type Rep (Syntax' ty) 
Instance details

Defined in Swarm.Language.Syntax.AST

type Rep (Syntax' ty) = D1 ('MetaData "Syntax'" "Swarm.Language.Syntax.AST" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Syntax'" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SrcLoc) :*: S1 ('MetaSel ('Just "_sTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Term' ty))) :*: (S1 ('MetaSel ('Just "_sComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Comments) :*: S1 ('MetaSel ('Just "_sType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ty))))

Methods

from :: Syntax' ty -> Rep (Syntax' ty) x #

to :: Rep (Syntax' ty) x -> Syntax' ty #

Show ty => Show (Syntax' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

showsPrec :: Int -> Syntax' ty -> ShowS #

show :: Syntax' ty -> String #

showList :: [Syntax' ty] -> ShowS #

Eq ty => Eq (Syntax' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

(==) :: Syntax' ty -> Syntax' ty -> Bool #

(/=) :: Syntax' ty -> Syntax' ty -> Bool #

Hashable ty => Hashable (Syntax' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

hashWithSalt :: Int -> Syntax' ty -> Int #

hash :: Syntax' ty -> Int #

Data ty => Plated (Syntax' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

plate :: Traversal' (Syntax' ty) (Syntax' ty) #

PrettyPrec (Syntax' ty)

Pretty-print a syntax node with comments.

Instance details

Defined in Swarm.Language.Syntax.Pretty

Methods

prettyPrec :: Int -> Syntax' ty -> Doc ann

type Rep (Syntax' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

type Rep (Syntax' ty) = D1 ('MetaData "Syntax'" "Swarm.Language.Syntax.AST" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Syntax'" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SrcLoc) :*: S1 ('MetaSel ('Just "_sTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Term' ty))) :*: (S1 ('MetaSel ('Just "_sComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Comments) :*: S1 ('MetaSel ('Just "_sType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ty))))

sLoc :: forall ty f. Functor f => (SrcLoc -> f SrcLoc) -> Syntax' ty -> f (Syntax' ty) Source #

sTerm :: forall ty f. Functor f => (Term' ty -> f (Term' ty)) -> Syntax' ty -> f (Syntax' ty) Source #

sType :: forall ty f. Functor f => (ty -> f ty) -> Syntax' ty -> f (Syntax' ty) Source #

sComments :: forall ty f. Functor f => (Comments -> f Comments) -> Syntax' ty -> f (Syntax' ty) Source #

type Syntax = Syntax' () Source #

Syntax without type annotations.

pattern Syntax :: SrcLoc -> Term -> Syntax Source #

Raw parsed syntax, without comments or type annotations.

pattern CSyntax :: SrcLoc -> Term -> Comments -> Syntax Source #

Untyped syntax with assocated comments.

data Located v Source #

A variable with associated source location, used for variable binding sites. (Variable occurrences are a bare TVar which gets wrapped in a Syntax node, so we don't need LocVar for those.)

Constructors

LV 

Fields

Instances

Instances details
Functor Located Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

fmap :: (a -> b) -> Located a -> Located b #

(<$) :: a -> Located b -> Located a #

FromJSON v => FromJSON (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

ToJSON v => ToJSON (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Data v => Data (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

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

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

toConstr :: Located v -> Constr #

dataTypeOf :: Located v -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Associated Types

type Rep (Located v) 
Instance details

Defined in Swarm.Language.Syntax.Loc

type Rep (Located v) = D1 ('MetaData "Located" "Swarm.Language.Syntax.Loc" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "LV" 'PrefixI 'True) (S1 ('MetaSel ('Just "lvSrcLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SrcLoc) :*: S1 ('MetaSel ('Just "lvVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 v)))

Methods

from :: Located v -> Rep (Located v) x #

to :: Rep (Located v) x -> Located v #

Show v => Show (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

showsPrec :: Int -> Located v -> ShowS #

show :: Located v -> String #

showList :: [Located v] -> ShowS #

Eq v => Eq (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

(==) :: Located v -> Located v -> Bool #

(/=) :: Located v -> Located v -> Bool #

Ord v => Ord (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

compare :: Located v -> Located v -> Ordering #

(<) :: Located v -> Located v -> Bool #

(<=) :: Located v -> Located v -> Bool #

(>) :: Located v -> Located v -> Bool #

(>=) :: Located v -> Located v -> Bool #

max :: Located v -> Located v -> Located v #

min :: Located v -> Located v -> Located v #

Hashable v => Hashable (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

Methods

hashWithSalt :: Int -> Located v -> Int #

hash :: Located v -> Int #

type Rep (Located v) Source # 
Instance details

Defined in Swarm.Language.Syntax.Loc

type Rep (Located v) = D1 ('MetaData "Located" "Swarm.Language.Syntax.Loc" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "LV" 'PrefixI 'True) (S1 ('MetaSel ('Just "lvSrcLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SrcLoc) :*: S1 ('MetaSel ('Just "lvVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 v)))

data LetSyntax Source #

A let expression can be written either as let x = e1 in e2 or as def x = e1 end; e2. This enumeration simply records which it was so that we can pretty-print appropriately.

Constructors

LSLet 
LSDef 

Instances

Instances details
FromJSON LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

ToJSON LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Data LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

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

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

toConstr :: LetSyntax -> Constr #

dataTypeOf :: LetSyntax -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Enum LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Generic LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Associated Types

type Rep LetSyntax 
Instance details

Defined in Swarm.Language.Syntax.AST

type Rep LetSyntax = D1 ('MetaData "LetSyntax" "Swarm.Language.Syntax.AST" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "LSLet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSDef" 'PrefixI 'False) (U1 :: Type -> Type))
Show LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Eq LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Ord LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Hashable LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

type Rep LetSyntax Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

type Rep LetSyntax = D1 ('MetaData "LetSyntax" "Swarm.Language.Syntax.AST" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "LSLet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSDef" 'PrefixI 'False) (U1 :: Type -> Type))

pattern STerm :: Term -> Syntax Source #

Match an untyped term without annotations.

pattern TRequirements :: Text -> Term -> Term Source #

pattern TPair :: Term -> Term -> Term Source #

Match a TPair without annotations.

pattern TLam :: Var -> Maybe Type -> Term -> Term Source #

Match a TLam without annotations.

pattern TApp :: Term -> Term -> Term Source #

Match a TApp without annotations.

pattern (:$:) :: Term -> Syntax -> Term infixl 0 Source #

Convenient infix pattern synonym for application.

pattern TLet :: LetSyntax -> Bool -> Var -> Maybe RawPolytype -> Maybe Polytype -> Maybe Requirements -> Term -> Term -> Term Source #

Match a TLet without annotations.

pattern TTydef :: TDVar -> Polytype -> Maybe TydefInfo -> Term -> Term Source #

Match a STydef without annotations.

pattern TBind :: Maybe Var -> Maybe Polytype -> Maybe Requirements -> Term -> Term -> Term Source #

Match a TBind without annotations.

pattern TDelay :: Term -> Term Source #

Match a TDelay without annotations.

pattern TRcd :: Map Var (Maybe Term) -> Term Source #

Match a TRcd without annotations.

pattern TProj :: Term -> Var -> Term Source #

pattern TAnnotate :: Term -> RawPolytype -> Term Source #

Match a TAnnotate without annotations.

pattern TSuspend :: Term -> Term Source #

Match a TSuspend without annotations.

pattern TParens :: Term -> Term Source #

Match a TParens without annotations.

Terms

type Var = Text Source #

For now, we just use Text to represent variables. In theory, at some point in the future we might want to represent them in some fancier way.

data Term' ty Source #

Terms of the Swarm language.

Constructors

TUnit

The unit value.

TConst Const

A constant.

TDir Direction

A direction literal.

TInt Integer

An integer literal.

TAntiInt Text

An antiquoted Haskell variable name of type Integer.

TText Text

A text literal.

TAntiText Text

An antiquoted Haskell variable name of type Text.

TBool Bool

A Boolean literal.

TAntiSyn Text

An antiquoted Haskell variable name of type Syntax.

TRobot Int

A robot reference. These never show up in surface syntax, but are here so we can factor pretty-printing for Values through pretty-printing for Terms.

TRef Int

A memory reference. These likewise never show up in surface syntax, but are here to facilitate pretty-printing.

TRequire Text

Require a specific device to be installed.

TStock Int Text

Require a certain number of an entity.

SRequirements Text (Syntax' ty)

Primitive command to log requirements of a term. The Text field is to store the unaltered original text of the term, for use in displaying the log message (since once we get to execution time the original term may have been elaborated, e.g. force may have been added around some variables, etc.)

TVar Var

A variable.

SPair (Syntax' ty) (Syntax' ty)

A pair.

SLam LocVar (Maybe Type) (Syntax' ty)

A lambda expression, with or without a type annotation on the binder.

SApp (Syntax' ty) (Syntax' ty)

Function application.

SLet LetSyntax Bool LocVar (Maybe RawPolytype) (Maybe Polytype) (Maybe Requirements) (Syntax' ty) (Syntax' ty)

A (recursive) let/def expression, with or without a type annotation on the variable. The Bool indicates whether it is known to be recursive.

The Maybe Polytype and Maybe Requirements fields are only for annotating the requirements of a definition after typechecking; there is no way to annotate requirements in the surface syntax.

STydef (Located TDVar) Polytype (Maybe TydefInfo) (Syntax' ty)

A type synonym definition. Note that this acts like a let (just like def), i.e. the Syntax' ty field is the local context over which the type definition is in scope.

SBind (Maybe LocVar) (Maybe ty) (Maybe Polytype) (Maybe Requirements) (Syntax' ty) (Syntax' ty)

A monadic bind for commands, of the form c1 ; c2 or x <- c1; c2.

The Maybe ty field is a place to stash the inferred type of the variable (if any) during type inference. Once type inference is complete, during elaboration we will copy the inferred type into the Maybe Polytype field (since the Maybe ty field will be erased).

The Maybe Polytype and Maybe Requirements fields is only for annotating the type of a bind after typechecking; there is no surface syntax that allows directly annotating a bind with either one.

SDelay (Syntax' ty)

Delay evaluation of a term, written {...}. Swarm is an eager language, but in some cases (e.g. for if statements and recursive bindings) we need to delay evaluation. The counterpart to {...} is force, where force {t} = t. Note that Force is just a constant, whereas SDelay has to be a special syntactic form so its argument can get special treatment during evaluation.

SRcd (Map Var (Maybe (Syntax' ty)))

Record literals [x1 = e1, x2 = e2, x3, ...] Names x without an accompanying definition are sugar for writing x=x.

SProj (Syntax' ty) Var

Record projection e.x

SAnnotate (Syntax' ty) RawPolytype

Annotate a term with a type

SSuspend (Syntax' ty)

Run the given command, then suspend and wait for a new REPL input.

SParens (Syntax' ty)

An explicit representation of parentheses in the input. We need this to be able to print formatted code with parentheses and comments preserved, but we get rid of them during elaboration.

TType Type

A type literal.

Instances

Instances details
FromJSON Term Source # 
Instance details

Defined in Swarm.Language.JSON

ToJSON Term Source # 
Instance details

Defined in Swarm.Language.JSON

Foldable Term' Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

fold :: Monoid m => Term' m -> m #

foldMap :: Monoid m => (a -> m) -> Term' a -> m #

foldMap' :: Monoid m => (a -> m) -> Term' a -> m #

foldr :: (a -> b -> b) -> b -> Term' a -> b #

foldr' :: (a -> b -> b) -> b -> Term' a -> b #

foldl :: (b -> a -> b) -> b -> Term' a -> b #

foldl' :: (b -> a -> b) -> b -> Term' a -> b #

foldr1 :: (a -> a -> a) -> Term' a -> a #

foldl1 :: (a -> a -> a) -> Term' a -> a #

toList :: Term' a -> [a] #

null :: Term' a -> Bool #

length :: Term' a -> Int #

elem :: Eq a => a -> Term' a -> Bool #

maximum :: Ord a => Term' a -> a #

minimum :: Ord a => Term' a -> a #

sum :: Num a => Term' a -> a #

product :: Num a => Term' a -> a #

Traversable Term' Source #

The Traversable instance for Term (and for Syntax') is used during typechecking: during intermediate type inference, many of the type annotations placed on AST nodes will have unification variables in them. Once we have finished solving everything we need to do a final traversal over all the types in the AST to substitute away all the unification variables (and generalize, i.e. stick forall on, as appropriate). See the call to mapM in Swarm.Language.Typecheck.runInfer.

Instance details

Defined in Swarm.Language.Syntax.AST

Methods

traverse :: Applicative f => (a -> f b) -> Term' a -> f (Term' b) #

sequenceA :: Applicative f => Term' (f a) -> f (Term' a) #

mapM :: Monad m => (a -> m b) -> Term' a -> m (Term' b) #

sequence :: Monad m => Term' (m a) -> m (Term' a) #

Functor Term' Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

fmap :: (a -> b) -> Term' a -> Term' b #

(<$) :: a -> Term' b -> Term' a #

Data ty => Data (Term' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Term' ty -> c (Term' ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Term' ty) #

toConstr :: Term' ty -> Constr #

dataTypeOf :: Term' ty -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Term' ty -> Term' ty #

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

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

gmapQ :: (forall d. Data d => d -> u) -> Term' ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Term' ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Term' ty -> m (Term' ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Term' ty -> m (Term' ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Term' ty -> m (Term' ty) #

Generic (Term' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Associated Types

type Rep (Term' ty) 
Instance details

Defined in Swarm.Language.Syntax.AST

type Rep (Term' ty) = D1 ('MetaData "Term'" "Swarm.Language.Syntax.AST" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) ((((C1 ('MetaCons "TUnit" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Const)) :+: C1 ('MetaCons "TDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Direction)))) :+: ((C1 ('MetaCons "TInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)) :+: C1 ('MetaCons "TAntiInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "TText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "TAntiText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))) :+: ((C1 ('MetaCons "TBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :+: (C1 ('MetaCons "TAntiSyn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "TRobot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))) :+: ((C1 ('MetaCons "TRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "TRequire" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "TStock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "SRequirements" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))))))) :+: (((C1 ('MetaCons "TVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Var)) :+: (C1 ('MetaCons "SPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))) :+: C1 ('MetaCons "SLam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LocVar) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Type)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))))) :+: ((C1 ('MetaCons "SApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))) :+: C1 ('MetaCons "SLet" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LetSyntax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LocVar) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RawPolytype)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Polytype)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Requirements))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))))) :+: (C1 ('MetaCons "STydef" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Located TDVar)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Polytype)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TydefInfo)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))) :+: C1 ('MetaCons "SBind" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LocVar)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Polytype)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Requirements)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))))))) :+: ((C1 ('MetaCons "SDelay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))) :+: (C1 ('MetaCons "SRcd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map Var (Maybe (Syntax' ty))))) :+: C1 ('MetaCons "SProj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Var)))) :+: ((C1 ('MetaCons "SAnnotate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RawPolytype)) :+: C1 ('MetaCons "SSuspend" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))) :+: (C1 ('MetaCons "SParens" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))) :+: C1 ('MetaCons "TType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)))))))

Methods

from :: Term' ty -> Rep (Term' ty) x #

to :: Rep (Term' ty) x -> Term' ty #

Show ty => Show (Term' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

showsPrec :: Int -> Term' ty -> ShowS #

show :: Term' ty -> String #

showList :: [Term' ty] -> ShowS #

Eq ty => Eq (Term' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

(==) :: Term' ty -> Term' ty -> Bool #

(/=) :: Term' ty -> Term' ty -> Bool #

Hashable ty => Hashable (Term' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

hashWithSalt :: Int -> Term' ty -> Int #

hash :: Term' ty -> Int #

Data ty => Plated (Term' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

Methods

plate :: Traversal' (Term' ty) (Term' ty) #

PrettyPrec (Term' ty) 
Instance details

Defined in Swarm.Language.Syntax.Pretty

Methods

prettyPrec :: Int -> Term' ty -> Doc ann

type Rep (Term' ty) Source # 
Instance details

Defined in Swarm.Language.Syntax.AST

type Rep (Term' ty) = D1 ('MetaData "Term'" "Swarm.Language.Syntax.AST" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) ((((C1 ('MetaCons "TUnit" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Const)) :+: C1 ('MetaCons "TDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Direction)))) :+: ((C1 ('MetaCons "TInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)) :+: C1 ('MetaCons "TAntiInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "TText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "TAntiText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))) :+: ((C1 ('MetaCons "TBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :+: (C1 ('MetaCons "TAntiSyn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "TRobot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))) :+: ((C1 ('MetaCons "TRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "TRequire" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "TStock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "SRequirements" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))))))) :+: (((C1 ('MetaCons "TVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Var)) :+: (C1 ('MetaCons "SPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))) :+: C1 ('MetaCons "SLam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LocVar) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Type)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))))) :+: ((C1 ('MetaCons "SApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))) :+: C1 ('MetaCons "SLet" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LetSyntax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LocVar) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RawPolytype)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Polytype)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Requirements))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))))) :+: (C1 ('MetaCons "STydef" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Located TDVar)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Polytype)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TydefInfo)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))) :+: C1 ('MetaCons "SBind" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LocVar)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Polytype)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Requirements)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))))))) :+: ((C1 ('MetaCons "SDelay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))) :+: (C1 ('MetaCons "SRcd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map Var (Maybe (Syntax' ty))))) :+: C1 ('MetaCons "SProj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Var)))) :+: ((C1 ('MetaCons "SAnnotate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RawPolytype)) :+: C1 ('MetaCons "SSuspend" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty)))) :+: (C1 ('MetaCons "SParens" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Syntax' ty))) :+: C1 ('MetaCons "TType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)))))))

type Term = Term' () Source #

mkOp :: Const -> (SrcLoc, t) -> Syntax -> Syntax -> Syntax Source #

Make an infix operation (e.g. 2 + 3) a curried function application (e.g. ((+) 2) 3).

mkOp' :: Const -> Term -> Term -> Term Source #

Make an infix operation, discarding any location information

unfoldApps :: Syntax' ty -> NonEmpty (Syntax' ty) Source #

Turn function application chain into a list.

>>> syntaxWrap f = fmap (^. sTerm) . f . Syntax NoLoc
>>> syntaxWrap unfoldApps (mkOp' Mul (TInt 1) (TInt 2)) -- 1 * 2
TConst Mul :| [TInt 1,TInt 2]

mkTuple :: [Syntax] -> Term Source #

Create an appropriate Term out of a list of syntax nodes which were enclosed with parentheses (and separated by commas).

unTuple :: Syntax' ty -> [Syntax' ty] Source #

Decompose a nested tuple into a list of components.

Erasure

erase :: Functor t => t ty -> t () Source #

Erase the type annotations from a Syntax or Term tree.

eraseS :: Syntax' ty -> Term Source #

Erase all annotations from a Syntax node, turning it into a bare Term.

Term traversal

freeVarsS :: forall ty f. Applicative f => (Syntax' ty -> f (Syntax' ty)) -> Syntax' ty -> f (Syntax' ty) Source #

Traversal over those subterms of a term which represent free variables. The S suffix indicates that it is a Traversal over the Syntax nodes (which contain type and source location info) containing free variables inside a larger Syntax value. Note that if you want to get the list of all Syntax nodes representing free variables, you can do so via toListOf freeVarsS.

freeVarsT :: forall ty f. Applicative f => (Term' ty -> f (Term' ty)) -> Syntax' ty -> f (Syntax' ty) Source #

Like freeVarsS, but traverse over the Terms containing free variables. More direct if you don't need to know the types or source locations of the variables. Note that if you want to get the list of all Terms representing free variables, you can do so via toListOf freeVarsT.

freeVarsV :: forall ty f. Applicative f => (Var -> f Var) -> Syntax' ty -> f (Syntax' ty) Source #

Traversal over the free variables of a term. Like freeVarsS and freeVarsT, but traverse over the variable names themselves. Note that if you want to get the set of all free variable names, you can do so via setOf freeVarsV.

mapFreeS :: Var -> (Syntax' ty -> Syntax' ty) -> Syntax' ty -> Syntax' ty Source #

Apply a function to all free occurrences of a particular variable.

asTree :: Data a => Syntax' a -> Tree (Syntax' a) Source #

Transform the AST into a Tree datatype. Useful for pretty-printing (e.g. via "Data.Tree.drawTree").

measureAstSize :: Data a => Syntax' a -> Int Source #

Each constructor is a assigned a value of 1, plus any recursive syntax it entails.