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

PortabilityGHC
Stabilityhighly unstable
Maintainerstephen.tetley@gmail.com

Wumpus.Basic.Kernel.Base.ContextFun

Contents

Description

Function types operating over the DrawingContext as a static argument.

Synopsis

Context functional types

data CF a Source

Most drawing operations in Wumpus-Basic have an implicit graphics state the DrawingContext, so the most primitive building block is a function from the DrawingContext to some polymorphic answer.

This functional type is represented concretely as the initials CF for contextual function.

 CF :: DrawingContext -> a 

Instances

data CF1 r1 a Source

Variation of CF with one parametric static argument.

The static argument is commonly a point representing the start point / origin of a drawing.

 CF1 :: DrawingContext -> r1 -> a 

Instances

Monad (CF1 r1) 
Functor (CF1 r1) 
Applicative (CF1 r1) 
DrawingCtxM (CF1 r1) 
Monoid a => Monoid (CF1 r1 a) 
OPlus a => OPlus (CF1 r1 a) 

data CF2 r1 r2 a Source

Variation of CF with two parametric static arguments.

The first argument is commonly a point representing the start point / origin of a drawing. The second argument might typically be the angle of displacement (for drawing arrowheads) or an end point (for drawing connectors between two points).

 CF2 :: DrawingContext -> r1 -> r2 -> a 

Instances

Monad (CF2 r1 r2) 
Functor (CF2 r1 r2) 
Applicative (CF2 r1 r2) 
DrawingCtxM (CF2 r1 r2) 
Monoid a => Monoid (CF2 r1 r2 a) 
OPlus a => OPlus (CF2 r1 r2 a) 

type LocCF u a = CF1 (Point2 u) aSource

Type specialized verison of CF1 where the static argument is the start point.

 LocCF :: DrawingContext -> Point2 u -> a 

type LocThetaCF u a = CF2 (Point2 u) Radian aSource

Type specialized verison of CF2 where the static arguments are the start point and the angle of displacement.

 LocThetaCF :: DrawingContext -> Point2 u -> Radian -> a 

type ConnectorCF u a = CF2 (Point2 u) (Point2 u) aSource

Type specialized verison of CF2 where the static arguments are the start point and the end point.

 ConnectorCF :: DrawingContext -> Point2 u -> Point2 u -> a 

type DLocCF a = LocCF Double aSource

Alias of LocCF where the unit type is specialized to Double.

type DLocThetaCF a = LocThetaCF Double aSource

Alias of LocThetaCF where the unit type is specialized to Double.

type DConnectorCF a = ConnectorCF Double aSource

Alias of ConnectorCF where the unit type is specialized to Double.

Run functions

runCF :: DrawingContext -> CF a -> aSource

Run a CF (context function) with the supplied DrawingContext.

runCF1 :: DrawingContext -> r1 -> CF1 r1 a -> aSource

Run a CF1 (context function) with the supplied DrawingContext and static argument.

runCF2 :: DrawingContext -> r1 -> r2 -> CF2 r1 r2 a -> aSource

Run a CF1 (context function) with the supplied DrawingContext and two static arguments.

Lift functions

lift0R1 :: CF a -> CF1 r1 aSource

Lift a zero-arity context function CF to an arity one context function CF1.

lift0R2 :: CF a -> CF2 r1 r2 aSource

Lift a zero-arity context function CF to an arity two context function CF2.

lift1R2 :: CF1 r1 a -> CF2 r1 r2 aSource

Lift an arity one context function CF1 to an arity two context function CF2.

promoteR1 :: (r1 -> CF a) -> CF1 r1 aSource

Promote a function from one argument to a Context Function to an arity one Context Function.

The type signature is as explanatory as a description:

 promoteR1 :: (r1 -> CF a) -> CF1 r1 a

promoteR2 :: (r1 -> r2 -> CF a) -> CF2 r1 r2 aSource

Promote a function from two arguments to a Context Function to an arity two Context Function.

The type signature is as explanatory as a description:

 promoteR2 :: (r1 -> r2 -> CF a) -> CF2 r1 r2 a

apply1R1 :: CF1 r1 a -> r1 -> CF aSource

Apply an arity-one Context Function to a single argument, downcasting it by one level, making an arity-zero Context function.

The type signature is as explanatory as a description:

 apply1R1 :: CF1 r1 a -> r1 -> CF a

apply2R2 :: CF2 r1 r2 a -> r1 -> r2 -> CF aSource

Apply an arity-two Context Function to two arguments, downcasting it by two levels, making an arity-zero Context function.

The type signature is as explanatory as a description:

 apply2R2 :: CF2 r1 r2 a -> r1 -> r2 -> CF a

apply1R2 :: CF2 r1 r2 a -> r2 -> CF1 r1 aSource

Apply an arity-two Context Function to one argument, downcasting it by one level, making an arity-one Context function.

The type signature is as explanatory as a description:

 apply1R2 :: CF2 r1 r2 a -> r2 -> CF1 r1 a

Extractors

drawingCtx :: CF DrawingContextSource

Extract the drawing context from a CtxFun.

 (ctx -> ctx)

queryCtx :: (DrawingContext -> a) -> CF aSource

Apply the projection function to the drawing context.

 (ctx -> a) -> (ctx -> a)

locCtx :: LocCF u DrawingContextSource

Extract the drawing context from a LocCF.

 (ctx -> pt -> ctx)

locPoint :: LocCF u (Point2 u)Source

Extract the start point from a LocCF.

 (ctx -> pt -> pt)

locThetaCtx :: LocThetaCF u DrawingContextSource

Extract the drawing context from a LocThetaCF.

 (ctx -> pt -> ang -> ctx)

locThetaPoint :: LocThetaCF u (Point2 u)Source

Extract the start point from a LocThetaCF.

 (ctx -> pt -> ang -> pt)

locThetaAng :: LocThetaCF u RadianSource

Extract the angle from a LocThetaCF.

 (ctx -> pt -> ang -> ang)

connCtx :: ConnectorCF u DrawingContextSource

Extract the drawing context from a ConnectorCF.

 (ctx -> pt1 -> pt2 -> ctx)

connStart :: ConnectorCF u (Point2 u)Source

Extract the start point from a ConnectorCF.

 (ctx -> pt1 -> pt2 -> pt1)

connEnd :: ConnectorCF u (Point2 u)Source

Extract the end point from a ConnectorCF.

 (ctx -> pt1 -> pt2 -> pt2)

Combinators

at :: LocCF u a -> Point2 u -> CF aSource

Downcast a LocCF function by applying it to the supplied point, making an arity-zero Context Function.

Remember a LocCF function is a CF1 context function where the static argument is specialized to a start point.

rot :: LocThetaCF u a -> Radian -> LocCF u aSource

Downcast a LocThetaCF function by applying it to the supplied angle, making an arity-one Context Function (a LocCF).

atRot :: LocThetaCF u a -> Point2 u -> Radian -> CF aSource

Downcast a LocThetaCF function by applying it to the supplied point and angle, making an arity-zero Context Function (a CF).

connect :: ConnectorCF u a -> Point2 u -> Point2 u -> CF aSource

Downcast a ConnectorCF function by applying it to the start and end point, making an arity-zero Context Function (a CF).

chain1 :: OPlus w => CF1 s1 (s1, w) -> CF1 s1 (s1, w) -> CF1 s1 (s1, w)Source

Chaining combinator - the answer of the first Context Function is feed to the second Context Function.

This contrasts with the usual idiom in Wumpus-Basic where composite graphics are built by applying both functions to the same initial static argument.

Desciption:

Evaluate the first Context Function with the drawing context and the initial state st0. The result of the evaluation is a new state st1 and and answer a1.

Evaluate the second Context Function with the drawing context and the new state st1, producing a new state s2 and an answer a2.

Return the result of combining the answers with op :: (ans -> ans -> ans) and the second state s2.

 (ctx -> s1 -> (w,s1)) -> (ctx -> s1 -> (w,s1)) -> (ctx -> s1 -> (w,s1))

This models chaining start points together, which is the model PostScript uses for text output when successively calling the show operator.