codeworld-api-0.1.0.1: Graphics library for CodeWorld

Safe HaskellNone
LanguageHaskell98

CodeWorld

Contents

Synopsis

Entry points

drawingOf :: Picture -> IO () Source #

Draws a Picture. This is the simplest CodeWorld entry point.

pictureOf :: Picture -> IO () Source #

Warning: Please use drawingOf instead of pictureOf

Draws a Picture. This is the simplest CodeWorld entry point.

animationOf :: (Double -> Picture) -> IO () Source #

Shows an animation, with a picture for each time given by the parameter.

simulationOf :: world -> (Double -> world -> world) -> (world -> Picture) -> IO () Source #

Shows a simulation, which is essentially a continuous-time dynamical system described by an initial value and step function.

interactionOf :: world -> (Double -> world -> world) -> (Event -> world -> world) -> (world -> Picture) -> IO () Source #

Runs an interactive event-driven CodeWorld program. This is the most advanced CodeWorld entry point.

Pictures

data TextStyle Source #

Constructors

Plain 
Bold 
Italic 

blank :: Picture Source #

A blank picture

line :: [Point] -> Picture Source #

Warning: Please use path instead of line

A thin sequence of line segments, with these points as endpoints

thickLine :: Double -> [Point] -> Picture Source #

Warning: Please use thickPath instead of thickLine

A thick sequence of line segments, with this line width and endpoints

path :: [Point] -> Picture Source #

A thin sequence of line segments, with these points as endpoints

thickPath :: Double -> [Point] -> Picture Source #

A thick sequence of line segments, with given line width and endpoints

polygon :: [Point] -> Picture Source #

A thin polygon with these points as vertices

thickPolygon :: Double -> [Point] -> Picture Source #

A thick polygon with this line width and these points as vertices

solidPolygon :: [Point] -> Picture Source #

A solid polygon with these points as vertices

curve :: [Point] -> Picture Source #

A smooth curve passing through these points.

thickCurve :: Double -> [Point] -> Picture Source #

A thick smooth curve with this line width, passing through these points.

loop :: [Point] -> Picture Source #

A smooth closed loop passing through these points.

thickLoop :: Double -> [Point] -> Picture Source #

A thick smooth closed loop with this line width, passing through these points.

solidLoop :: [Point] -> Picture Source #

A solid smooth closed loop passing through these points.

rectangle :: Double -> Double -> Picture Source #

A thin rectangle, with this width and height

solidRectangle :: Double -> Double -> Picture Source #

A solid rectangle, with this width and height

thickRectangle :: Double -> Double -> Double -> Picture Source #

A thick rectangle, with this line width, and width and height

circle :: Double -> Picture Source #

A thin circle, with this radius

solidCircle :: Double -> Picture Source #

A solid circle, with this radius

thickCircle :: Double -> Double -> Picture Source #

A thick circle, with this line width and radius

arc :: Double -> Double -> Double -> Picture Source #

A thin arc, starting and ending at these angles, with this radius

Angles are in radians.

sector :: Double -> Double -> Double -> Picture Source #

A solid sector of a circle (i.e., a pie slice) starting and ending at these angles, with this radius

Angles are in radians.

thickArc :: Double -> Double -> Double -> Double -> Picture Source #

A thick arc with this line width, starting and ending at these angles, with this radius.

Angles are in radians.

text :: Text -> Picture Source #

A piece of text

colored :: Color -> Picture -> Picture Source #

A picture drawn entirely in this color.

coloured :: Color -> Picture -> Picture Source #

A picture drawn entirely in this color.

translated :: Double -> Double -> Picture -> Picture Source #

A picture drawn translated in these directions.

scaled :: Double -> Double -> Picture -> Picture Source #

A picture scaled by these factors.

dilated :: Double -> Double -> Picture -> Picture Source #

A picture scaled by these factors.

rotated :: Double -> Picture -> Picture Source #

A picture rotated by this angle.

Angles are in radians.

(&) :: Picture -> Picture -> Picture infixr 0 Source #

Warning: Please use <> from Data.Monoid instead of &

(<>) :: Monoid m => m -> m -> m infixr 6 #

An infix synonym for mappend.

Since: 4.5.0.0

coordinatePlane :: Picture Source #

A coordinate plane. Adding this to your pictures can help you measure distances more accurately.

Example:

main = pictureOf(myPicture & coordinatePlane) myPicture = ...

:: Picture Source #

The CodeWorld logo.

rotatedVector :: Double -> Vector -> Vector Source #

Angle is in radians

Colors

data Color Source #

Constructors

RGBA !Double !Double !Double !Double 

Instances

Eq Color Source # 

Methods

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

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

Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Events

data Event Source #

An event initiated by the user.

Values of this type represent events that the user triggers when using an interaction, defined with interactionOf.

Key events describe the key as Text. Most keys are represented by a single character text string, with the capital letter or other symbol from the key. Keys that don't correspond to a single character use longer names from the following list. Keep in mind that not all of these keys appear on all keyboards.

  • Up, Down, Left, and Right for the cursor keys.
  • F1, F2, etc. for function keys.
  • Backspace
  • Tab
  • Enter
  • Shift
  • Ctrl
  • Alt
  • Esc
  • PageUp
  • PageDown
  • End
  • Home
  • Insert
  • Delete
  • CapsLock
  • NumLock
  • ScrollLock
  • PrintScreen
  • Break
  • Separator
  • Cancel
  • Help

Instances

Eq Event Source # 

Methods

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

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

Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Debugging

trace :: Text -> a -> a Source #

Prints a debug message to the CodeWorld console when a value is forced. This is equivalent to the similarly named function in Trace, except that it uses the CodeWorld console instead of standard output.