swarm-0.5.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Game.World.Syntax

Description

Abstract syntax for the Swarm world description DSL.

Synopsis

Documentation

Various component types

type World b = Coords -> b Source #

data CellTag Source #

Instances

Instances details
Bounded CellTag Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Enum CellTag Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Show CellTag Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Eq CellTag Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

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

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

Ord CellTag Source # 
Instance details

Defined in Swarm.Game.World.Syntax

PrettyPrec CellTag Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

prettyPrec :: Int -> CellTag -> Doc ann Source #

data CellVal Source #

Instances

Instances details
Show CellVal Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Eq CellVal Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

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

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

Empty CellVal Source # 
Instance details

Defined in Swarm.Game.World.Typecheck

Methods

empty :: CellVal Source #

Over CellVal Source # 
Instance details

Defined in Swarm.Game.World.Typecheck

PrettyPrec CellVal Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

prettyPrec :: Int -> CellVal -> Doc ann Source #

data Rot Source #

Constructors

Rot0 
Rot90 
Rot180 
Rot270 

Instances

Instances details
Bounded Rot Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

minBound :: Rot #

maxBound :: Rot #

Enum Rot Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

succ :: Rot -> Rot #

pred :: Rot -> Rot #

toEnum :: Int -> Rot #

fromEnum :: Rot -> Int #

enumFrom :: Rot -> [Rot] #

enumFromThen :: Rot -> Rot -> [Rot] #

enumFromTo :: Rot -> Rot -> [Rot] #

enumFromThenTo :: Rot -> Rot -> Rot -> [Rot] #

Show Rot Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

showsPrec :: Int -> Rot -> ShowS #

show :: Rot -> String #

showList :: [Rot] -> ShowS #

Eq Rot Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

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

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

Ord Rot Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

compare :: Rot -> Rot -> Ordering #

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

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

(>) :: Rot -> Rot -> Bool #

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

max :: Rot -> Rot -> Rot #

min :: Rot -> Rot -> Rot #

PrettyPrec Rot Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

prettyPrec :: Int -> Rot -> Doc ann Source #

type Var = Text Source #

data Axis Source #

Constructors

X 
Y 

Instances

Instances details
Bounded Axis Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Enum Axis Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

succ :: Axis -> Axis #

pred :: Axis -> Axis #

toEnum :: Int -> Axis #

fromEnum :: Axis -> Int #

enumFrom :: Axis -> [Axis] #

enumFromThen :: Axis -> Axis -> [Axis] #

enumFromTo :: Axis -> Axis -> [Axis] #

enumFromThenTo :: Axis -> Axis -> Axis -> [Axis] #

Show Axis Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

showsPrec :: Int -> Axis -> ShowS #

show :: Axis -> String #

showList :: [Axis] -> ShowS #

Eq Axis Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

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

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

Ord Axis Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

compare :: Axis -> Axis -> Ordering #

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

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

(>) :: Axis -> Axis -> Bool #

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

max :: Axis -> Axis -> Axis #

min :: Axis -> Axis -> Axis #

PrettyPrec Axis Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

prettyPrec :: Int -> Axis -> Doc ann Source #

data Op Source #

Constructors

Not 
Neg 
And 
Or 
Add 
Sub 
Mul 
Div 
Mod 
Eq 
Neq 
Lt 
Leq 
Gt 
Geq 
If 
Perlin 
Reflect Axis 
Rot Rot 
Mask 
Overlay 
Abs 

Instances

Instances details
Show Op Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

Eq Op Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

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

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

Ord Op Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

compare :: Op -> Op -> Ordering #

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

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

(>) :: Op -> Op -> Bool #

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

max :: Op -> Op -> Op #

min :: Op -> Op -> Op #

The main AST type

data WExp where Source #

Constructors

WInt :: Integer -> WExp 
WFloat :: Double -> WExp 
WBool :: Bool -> WExp 
WCell :: RawCellVal -> WExp 
WVar :: Text -> WExp 
WOp :: Op -> [WExp] -> WExp 
WSeed :: WExp 
WCoord :: Axis -> WExp 
WHash :: WExp 
WLet :: [(Var, WExp)] -> WExp -> WExp 
WOverlay :: NonEmpty WExp -> WExp 
WImport :: Text -> WExp 

Instances

Instances details
FromJSON WExp Source # 
Instance details

Defined in Swarm.Game.World.Parse

Show WExp Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

showsPrec :: Int -> WExp -> ShowS #

show :: WExp -> String #

showList :: [WExp] -> ShowS #

Eq WExp Source # 
Instance details

Defined in Swarm.Game.World.Syntax

Methods

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

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