wumpus-basic-0.17.0: Basic objects and system code built on Wumpus-Core.

PortabilityGHC
Stabilityhighly unstable
Maintainerstephen.tetley@gmail.com

Wumpus.Basic.Kernel.Objects.PosObject

Contents

Description

Extended Graphic object - a rectangular positionable Image.

This graphic object has a more flexible API for positioning than other graphic objects. Rather than a LocGraphic which supports a single method of positioning at some start-point, a PosGraphic can be drawn at its center or locations on its outer rectangle.

Synopsis

Positionable image

data PosObject u Source

A positionable "Object" that is drawn as a BoundedLocGraphic.

Instances

(Fractional u, Ord u, InterpretUnit u) => Monoid (PosObject u) 
(Fractional u, Ord u) => OPlus (PosObject u) 
(Fractional u, Ord u) => AlignSpace (PosObject u) 
(Fractional u, Ord u) => Align (PosObject u) 
(Num u, Ord u) => CatSpace (PosObject u) 
(Num u, Ord u) => Concat (PosObject u) 
(Fractional u, Ord u) => ZConcat (PosObject u) 

type DPosObject = PosObject DoubleSource

Version of PosObject specialized to Double for the unit type.

type LocRectQuery u a = CF (Point2 u -> RectAddress -> a)Source

Operations

makePosObject :: Query (Orientation u) -> LocGraphic u -> PosObject uSource

makePosObject : object_pos * loc_image -> PosObject

Create a PosObject from an Orientation describing how it is orientated within a border rectangle and a LocImage that draws it.

This is the primary constructor for PosObjects. Because the PosObject type is considered as a specialized object it does not have the range of functions of LocImage or LocThetaImage.

makeBindPosObject :: Query a -> (a -> Query (Orientation u)) -> (a -> LocGraphic u) -> PosObject uSource

This is a bit of a hack to overcome that the newtype wrapper around PosObject stops monadic bind operating with the internal CF function.

emptyPosObject :: InterpretUnit u => PosObject uSource

emptyPosObject : PosObject

Build an empty PosGraphicObject.

runPosObjectR0 :: Fractional u => Point2 u -> RectAddress -> PosObject u -> BoundedGraphic uSource

Run a PosObject forming an Image (an arity zero answer).

runPosObjectR1 :: Fractional u => RectAddress -> PosObject u -> BoundedLocGraphic uSource

Version of runPosObject that produces a BoundedLocGraphic.

The PosObject is run with only rect-address as an explicit argument (start-point is implicit). The corresponding answer is an arity one Graphic that needs drawing with the start-point.

runPosObjectR2 :: Fractional u => PosObject u -> BoundedLocRectGraphic uSource

Version of runPosObject that produces a BoundedLocRectGraphic.

The PosObject is run with no explicit arguments (rect-address or start-point) so the corresponding answer is an arity two Graphic that needs drawing with the start-point and rect-address.

localizePO :: DrawingContextF -> PosObject u -> PosObject uSource

Run a DrawingContext update within a PosObject.

elaboratePO :: (Orientation u -> LocGraphic u) -> PosObject u -> PosObject uSource

decorate -like functionality.

aelaboratePO :: (Orientation u -> LocGraphic u) -> PosObject u -> PosObject uSource

ante-eloborate

startAddr :: Floating u => BoundedLocRectGraphic u -> RectAddress -> BoundedLocGraphic uSource

startAddr : bounded_loc_rect * rect_pos -> BoundedlocGraphic

Downcast a BoundedLocRectGraphic to a BoundedLocGraphic by supplying it with a RectAddress (start address on the rectangle frame).

atStartAddr :: Floating u => BoundedLocRectGraphic u -> Point2 u -> RectAddress -> BoundedGraphic uSource

atStartAddr : bounded_loc_rect * start_point * rect_pos -> BoundedGraphic

Downcast a BoundedLocRectGraphic to a BoundedGraphic by supplying it with an initial point and a RectAddress (start address on the rectangle frame).

extendPosObject :: Num u => u -> u -> u -> u -> PosObject u -> PosObject uSource

Extend the orientation.

padLeftPO :: (Num u, Ord u) => u -> PosObject u -> PosObject uSource

padRightPO :: (Num u, Ord u) => u -> PosObject u -> PosObject uSource

padUpPO :: (Num u, Ord u) => u -> PosObject u -> PosObject uSource

padDownPO :: (Num u, Ord u) => u -> PosObject u -> PosObject uSource

illustratePosObject :: InterpretUnit u => PosObject u -> LocGraphic uSource

Illustrate a PosObject by super-imposing its Orientation.

This turns the PosObject into a LocImage drawn at the locus of the PosObject.