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

Swarm.Language.Direction

Contents

Description

Types and helper functions for working with directions

Synopsis

Directions

data Direction Source #

The type of directions. Used e.g. to indicate which way a robot will turn.

Instances

Instances details
FromJSON Direction Source # 
Instance details

Defined in Swarm.Language.Direction

ToJSON Direction Source # 
Instance details

Defined in Swarm.Language.Direction

Data Direction Source # 
Instance details

Defined in Swarm.Language.Direction

Methods

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

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

toConstr :: Direction -> Constr #

dataTypeOf :: Direction -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Direction Source # 
Instance details

Defined in Swarm.Language.Direction

Associated Types

type Rep Direction :: Type -> Type #

Read Direction Source # 
Instance details

Defined in Swarm.Language.Direction

Show Direction Source # 
Instance details

Defined in Swarm.Language.Direction

Eq Direction Source # 
Instance details

Defined in Swarm.Language.Direction

Ord Direction Source # 
Instance details

Defined in Swarm.Language.Direction

Hashable Direction Source # 
Instance details

Defined in Swarm.Language.Direction

Valuable Direction Source # 
Instance details

Defined in Swarm.Game.Value

PrettyPrec Direction Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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

type Rep Direction Source # 
Instance details

Defined in Swarm.Language.Direction

type Rep Direction = D1 ('MetaData "Direction" "Swarm.Language.Direction" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "DAbsolute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AbsoluteDir)) :+: C1 ('MetaCons "DRelative" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RelativeDir)))

data AbsoluteDir Source #

An absolute direction is one which is defined with respect to an external frame of reference; robots need a compass in order to use them.

NOTE: These values are ordered by increasing angle according to the standard mathematical convention. That is, the right-pointing direction, East, is considered the "reference angle" and the order proceeds counter-clockwise. See https://en.wikipedia.org/wiki/Polar_coordinate_system#Conventions

Do not alter this ordering, as there exist functions that depend on it (e.g. nearestDirection and relativeTo).

Constructors

DEast 
DNorth 
DWest 
DSouth 

Instances

Instances details
FromJSON AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

FromJSONKey AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

ToJSON AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

ToJSONKey AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Data AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Methods

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

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

toConstr :: AbsoluteDir -> Constr #

dataTypeOf :: AbsoluteDir -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Enum AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Generic AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Associated Types

type Rep AbsoluteDir :: Type -> Type #

Read AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Show AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Eq AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Ord AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

Hashable AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

type Rep AbsoluteDir Source # 
Instance details

Defined in Swarm.Language.Direction

type Rep AbsoluteDir = D1 ('MetaData "AbsoluteDir" "Swarm.Language.Direction" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) ((C1 ('MetaCons "DEast" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DNorth" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DWest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DSouth" 'PrefixI 'False) (U1 :: Type -> Type)))

data RelativeDir Source #

A relative direction is one which is defined with respect to the robot's frame of reference; no special capability is needed to use them.

Instances

Instances details
FromJSON RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

ToJSON RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Data RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Methods

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

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

toConstr :: RelativeDir -> Constr #

dataTypeOf :: RelativeDir -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Associated Types

type Rep RelativeDir :: Type -> Type #

Read RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Show RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Eq RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Ord RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Hashable RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

type Rep RelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

type Rep RelativeDir = D1 ('MetaData "RelativeDir" "Swarm.Language.Direction" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "DPlanar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PlanarRelativeDir)) :+: C1 ('MetaCons "DDown" 'PrefixI 'False) (U1 :: Type -> Type))

data PlanarRelativeDir Source #

Caution: Do not alter this ordering, as there exist functions that depend on it (e.g. nearestDirection and relativeTo).

Constructors

DForward 
DLeft 
DBack 
DRight 

Instances

Instances details
FromJSON PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

ToJSON PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Data PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Methods

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

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

toConstr :: PlanarRelativeDir -> Constr #

dataTypeOf :: PlanarRelativeDir -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Enum PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Generic PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Associated Types

type Rep PlanarRelativeDir :: Type -> Type #

Read PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Show PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Eq PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Ord PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

Hashable PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

type Rep PlanarRelativeDir Source # 
Instance details

Defined in Swarm.Language.Direction

type Rep PlanarRelativeDir = D1 ('MetaData "PlanarRelativeDir" "Swarm.Language.Direction" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) ((C1 ('MetaCons "DForward" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DLeft" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DBack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DRight" 'PrefixI 'False) (U1 :: Type -> Type)))

directionSyntax :: Direction -> Text Source #

Direction name is generated from the deepest nested data constructor e.g. DLeft becomes "left"

isCardinal :: Direction -> Bool Source #

Check if the direction is absolute (e.g. north or south).