codeworld-api-0.8.1: Graphics library for CodeWorld

Safe HaskellNone
LanguageHaskell2010

CodeWorld

Contents

Synopsis

Entry points

drawingOf #

Arguments

:: Picture

The picture to show on the screen.

-> IO () 

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

Example: a program which draws a circle of radius 1 in the middle of canvas

main = drawingOf $ circle 1

animationOf #

Arguments

:: (Double -> Picture)

A function that produces animation frames, given the time in seconds.

-> IO () 

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

Example: a program showing a square which rotates once every two seconds

main = animationOf rotatingSquare

rotatingSquare :: Double -> Picture
rotatingSquare seconds = rotated angle square
  where
    square = rectangle 2 2
    angle = pi * seconds

activityOf #

Arguments

:: world

The initial state of the activity.

-> (Event -> world -> world)

The event handling function, which updates the state given an event.

-> (world -> Picture)

The visualization function, which converts the state into a picture to display.

-> IO () 

Runs an interactive CodeWorld program that responds to Events. Activities can interact with the user, change over time, and remember information about the past.

Example: a program which draws a circle and changes its radius when user presses Up or Down keys on her keyboard

 {-# LANGUAGE OverloadedStrings #-}
import CodeWorld

main = activityOf initialRadius updateRadius circle
   where
     initialRadius = 1

     updateRadius event radius =
       case event of
         KeyPress Up   -> radius + 1
         KeyPress Down -> radius - 1
         _               -> radius

debugActivityOf #

Arguments

:: world

The initial state of the interaction.

-> (Event -> world -> world)

The event handling function, which updates the state given an event.

-> (world -> Picture)

The visualization function, which converts the state into a picture to display.

-> IO () 

A version of activityOf which runs an interactive CodeWorld program in debugging mode. In this mode, the program gets controls to pause and manipulate time, and even go back in time to look at past states.

groupActivityOf #

Arguments

:: Int

The number of participants to expect. The participants will be numbered starting at 0.

-> StaticPtr (StdGen -> world)

The function to create initial state of the activity. StdGen parameter can be used to generate random numbers.

-> StaticPtr (Int -> Event -> world -> world)

The event handling function, which updates the state given a participant number and user interface event.

-> StaticPtr (Int -> world -> Picture)

The visualization function, which converts a participant number and the state into a picture to display.

-> IO () 

Runs an interactive multi-user CodeWorld program that is joined by several participants over the internet.

Example: a skeleton of a game for two players

{-# LANGUAGE StaticPointers, OverloadedStrings #-}
import CodeWorld

main = groupActivityOf 2 init step view
  where
    init = static (\gen -> {- initialize state of the game world, possibly using random number generator -})
    step = static (\playerNumber event world -> {- modify world based on event occuring for given player -})
    view = static (\playerNumber world -> {- generate a picture that will be shown to given player in the given state of the world-})

unsafeGroupActivityOf #

Arguments

:: Int

The number of participants to expect. The participants will be numbered starting at 0.

-> (StdGen -> world)

The initial state of the activity.

-> (Int -> Event -> world -> world)

The event handling function, which updates the state given a participant number and user interface event.

-> (Int -> world -> Picture)

The visualization function, which converts a participant number and the state into a picture to display.

-> IO () 

A version of groupActivityOf that avoids static pointers, and does not check for consistency.

Pictures

data Picture #

A design, diagram, or drawing that can be displayed and seen. In technical terms, a picture is an assignment of a color to every point of the coordinate plane. CodeWorld contains functions to create pictures from simple geometry primitives, to transform existing pictures, and to combine simpler pictures into more complex compositions.

Ultimately, a picture can be drawn on the screen using one of the CodeWorld entry points such as drawingOf.

Instances
Generic Picture # 
Instance details

Defined in CodeWorld.Picture

Associated Types

type Rep Picture :: Type -> Type

Methods

from :: Picture -> Rep Picture x

to :: Rep Picture x -> Picture

Semigroup Picture # 
Instance details

Defined in CodeWorld.Picture

Methods

(<>) :: Picture -> Picture -> Picture #

sconcat :: NonEmpty Picture -> Picture

stimes :: Integral b => b -> Picture -> Picture

Monoid Picture # 
Instance details

Defined in CodeWorld.Picture

NFData Picture # 
Instance details

Defined in CodeWorld.Picture

Methods

rnf :: Picture -> ()

type Rep Picture # 
Instance details

Defined in CodeWorld.Picture

type Rep Picture = D1 (MetaData "Picture" "CodeWorld.Picture" "codeworld-api-0.8.1-7T3tiJk8bGQ3u45lBcdj0s" False) (((((C1 (MetaCons "SolidPolygon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point])) :+: C1 (MetaCons "SolidClosedCurve" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point]))) :+: (C1 (MetaCons "Polygon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point])) :+: C1 (MetaCons "ThickPolygon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))))) :+: ((C1 (MetaCons "Rectangle" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: C1 (MetaCons "SolidRectangle" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))) :+: (C1 (MetaCons "ThickRectangle" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: C1 (MetaCons "ClosedCurve" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point]))))) :+: (((C1 (MetaCons "ThickClosedCurve" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: C1 (MetaCons "Polyline" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point]))) :+: (C1 (MetaCons "ThickPolyline" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: C1 (MetaCons "Curve" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point])))) :+: ((C1 (MetaCons "ThickCurve" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: C1 (MetaCons "Circle" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: (C1 (MetaCons "SolidCircle" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :+: C1 (MetaCons "ThickCircle" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))))))) :+: ((((C1 (MetaCons "Sector" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: C1 (MetaCons "Arc" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))) :+: (C1 (MetaCons "ThickArc" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))) :+: C1 (MetaCons "StyledLettering" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextStyle)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Font) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) :+: ((C1 (MetaCons "Lettering" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "Color" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Color) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Picture)))) :+: (C1 (MetaCons "Translate" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Picture))) :+: C1 (MetaCons "Scale" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Picture)))))) :+: (((C1 (MetaCons "Dilate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Picture))) :+: C1 (MetaCons "Rotate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Picture)))) :+: (C1 (MetaCons "Reflect" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Picture))) :+: C1 (MetaCons "Clip" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Picture))))) :+: ((C1 (MetaCons "CoordinatePlane" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc))) :+: C1 (MetaCons "Sketch" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))))) :+: (C1 (MetaCons "Pictures" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Picture])) :+: (C1 (MetaCons "PictureAnd" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Picture])) :+: C1 (MetaCons "Blank" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SrcLoc)))))))))

data TextStyle #

Constructors

Plain

Plain letters with no style

Bold

Heavy, thick lettering used for emphasis

Italic

Slanted script-like lettering used for emphasis

Instances
Show TextStyle # 
Instance details

Defined in CodeWorld.Picture

Methods

showsPrec :: Int -> TextStyle -> ShowS

show :: TextStyle -> String

showList :: [TextStyle] -> ShowS

Generic TextStyle # 
Instance details

Defined in CodeWorld.Picture

Associated Types

type Rep TextStyle :: Type -> Type

Methods

from :: TextStyle -> Rep TextStyle x

to :: Rep TextStyle x -> TextStyle

NFData TextStyle # 
Instance details

Defined in CodeWorld.Picture

Methods

rnf :: TextStyle -> ()

type Rep TextStyle # 
Instance details

Defined in CodeWorld.Picture

type Rep TextStyle = D1 (MetaData "TextStyle" "CodeWorld.Picture" "codeworld-api-0.8.1-7T3tiJk8bGQ3u45lBcdj0s" False) (C1 (MetaCons "Plain" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Bold" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Italic" PrefixI False) (U1 :: Type -> Type)))

data Font #

Instances
Show Font # 
Instance details

Defined in CodeWorld.Picture

Methods

showsPrec :: Int -> Font -> ShowS

show :: Font -> String

showList :: [Font] -> ShowS

Generic Font # 
Instance details

Defined in CodeWorld.Picture

Associated Types

type Rep Font :: Type -> Type

Methods

from :: Font -> Rep Font x

to :: Rep Font x -> Font

NFData Font # 
Instance details

Defined in CodeWorld.Picture

Methods

rnf :: Font -> ()

type Rep Font # 
Instance details

Defined in CodeWorld.Picture

type Rep Font = D1 (MetaData "Font" "CodeWorld.Picture" "codeworld-api-0.8.1-7T3tiJk8bGQ3u45lBcdj0s" False) ((C1 (MetaCons "SansSerif" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Serif" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Monospace" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Handwriting" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Fancy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NamedFont" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

blank :: HasCallStack => Picture #

A blank picture

polyline :: HasCallStack => [Point] -> Picture #

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

thickPolyline :: HasCallStack => Double -> [Point] -> Picture #

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

polygon :: HasCallStack => [Point] -> Picture #

A thin polygon with these points as vertices

thickPolygon :: HasCallStack => Double -> [Point] -> Picture #

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

solidPolygon :: HasCallStack => [Point] -> Picture #

A solid polygon with these points as vertices

curve :: HasCallStack => [Point] -> Picture #

A smooth curve passing through these points.

thickCurve :: HasCallStack => Double -> [Point] -> Picture #

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

closedCurve :: HasCallStack => [Point] -> Picture #

A smooth closed curve passing through these points.

thickClosedCurve :: HasCallStack => Double -> [Point] -> Picture #

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

solidClosedCurve :: HasCallStack => [Point] -> Picture #

A solid smooth closed curve passing through these points.

rectangle :: HasCallStack => Double -> Double -> Picture #

A thin rectangle, with this width and height

solidRectangle :: HasCallStack => Double -> Double -> Picture #

A solid rectangle, with this width and height

thickRectangle :: HasCallStack => Double -> Double -> Double -> Picture #

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

circle :: HasCallStack => Double -> Picture #

A thin circle, with this radius

solidCircle :: HasCallStack => Double -> Picture #

A solid circle, with this radius

thickCircle :: HasCallStack => Double -> Double -> Picture #

A thick circle, with this line width and radius

arc :: HasCallStack => Double -> Double -> Double -> Picture #

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

Angles are in radians.

sector :: HasCallStack => Double -> Double -> Double -> Picture #

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 :: HasCallStack => Double -> Double -> Double -> Double -> Picture #

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

Angles are in radians.

lettering :: HasCallStack => Text -> Picture #

A rendering of text characters.

styledLettering :: HasCallStack => TextStyle -> Font -> Text -> Picture #

A rendering of text characters onto a Picture, with a specific choice of font and style.

colored :: HasCallStack => Color -> Picture -> Picture #

A picture drawn entirely in this color.

coloured :: HasCallStack => Color -> Picture -> Picture #

A picture drawn entirely in this colour.

translated :: HasCallStack => Double -> Double -> Picture -> Picture #

A picture drawn translated in these directions.

scaled :: HasCallStack => Double -> Double -> Picture -> Picture #

A picture scaled by these factors in the x and y directions. Scaling by a negative factoralso reflects across that axis.

dilated :: HasCallStack => Double -> Picture -> Picture #

A picture scaled uniformly in all directions by this scale factor. Dilating by a negative factor also reflects across the origin.

rotated :: HasCallStack => Double -> Picture -> Picture #

A picture rotated by this angle about the origin.

Angles are in radians.

reflected :: HasCallStack => Double -> Picture -> Picture #

A picture reflected across a line through the origin at this angle, in radians. For example, an angle of 0 reflects the picture vertically across the x axis, while an angle of pi / 2 reflects the picture horizontally across the y axis.

clipped :: HasCallStack => Double -> Double -> Picture -> Picture #

A picture clipped to a rectangle around the origin with this width and height.

pictures :: HasCallStack => [Picture] -> Picture #

(<>) :: Semigroup a => a -> a -> a #

(&) :: HasCallStack => Picture -> Picture -> Picture infixr 0 #

Binary composition of pictures.

coordinatePlane :: HasCallStack => Picture #

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

Example: main = drawingOf (myPicture <> coordinatePlane) myPicture = ...

:: HasCallStack => Picture #

The CodeWorld logo.

type Point = (Double, Double) #

A point in two dimensions. A point is written with the x coordinate first, and the y coordinate second. For example, (3, -2) is the point with x coordinate 3 a y coordinate -2.

translatedPoint :: Double -> Double -> Point -> Point #

Moves a given point by given x and y offsets

>>> translatedPoint 1 2 (10, 10)
(11.0, 12.0)
>>> translatedPoint (-1) (-2) (0, 0)
(-1.0, -2.0)

rotatedPoint :: Double -> Point -> Point #

Rotates a given point by given angle, in radians

>>> rotatedPoint 45 (10, 0)
(7.071, 7.071)

reflectedPoint :: Double -> Point -> Point #

Reflects a given point across a line through the origin at this angle, in radians. For example, an angle of 0 reflects the point vertically across the x axis, while an angle of pi / 2 reflects the point horizontally across the y axis.

scaledPoint :: Double -> Double -> Point -> Point #

Scales a given point by given x and y scaling factor. Scaling by a negative factor also reflects across that axis.

>>> scaledPoint 2 3 (10, 10)
(20, 30)

dilatedPoint :: Double -> Point -> Point #

Dilates a given point by given uniform scaling factor. Dilating by a negative factor also reflects across the origin.

>>> dilatedPoint 2 (10, 10)
(20, 20)

type Vector = (Double, Double) #

A two-dimensional vector

vectorLength :: Vector -> Double #

The length of the given vector.

>>> vectorLength (10, 10)
14.14

vectorDirection :: Vector -> Double #

The counter-clockwise angle, in radians, that a given vector make with the X-axis

>>> vectorDirection (1,0)
0.0
>>> vectorDirection (1,1)
0.7853981633974483
>>> vectorDirection (0,1)
1.5707963267948966

vectorSum :: Vector -> Vector -> Vector #

The sum of two vectors

vectorDifference :: Vector -> Vector -> Vector #

The difference of two vectors

scaledVector :: Double -> Vector -> Vector #

Scales a given vector by a given scalar multiplier.

>>> scaledPoint 2 (10, 10)
(20, 20)

rotatedVector :: Double -> Vector -> Vector #

Rotates a given vector by a given angle in radians

>>> rotatedVector pi (1.0, 0.0)
(-1.0, 1.2246467991473532e-16)
>>> rotatedVector (pi / 2) (1.0, 0.0)
(6.123233995736766e-17, 1.0)

dotProduct :: Vector -> Vector -> Double #

The dot product of two vectors

Colors

data Color #

Constructors

RGBA !Double !Double !Double !Double 
Instances
Eq Color # 
Instance details

Defined in CodeWorld.Color

Methods

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

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

Show Color # 
Instance details

Defined in CodeWorld.Color

Methods

showsPrec :: Int -> Color -> ShowS

show :: Color -> String

showList :: [Color] -> ShowS

Generic Color # 
Instance details

Defined in CodeWorld.Color

Associated Types

type Rep Color :: Type -> Type

Methods

from :: Color -> Rep Color x

to :: Rep Color x -> Color

NFData Color # 
Instance details

Defined in CodeWorld.Color

Methods

rnf :: Color -> ()

type Rep Color # 
Instance details

Defined in CodeWorld.Color

type Rep Color = D1 (MetaData "Color" "CodeWorld.Color" "codeworld-api-0.8.1-7T3tiJk8bGQ3u45lBcdj0s" False) (C1 (MetaCons "RGBA" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))))

type Colour = Color #

pattern RGB :: Double -> Double -> Double -> Color #

pattern HSL :: Double -> Double -> Double -> Color #

mixed :: [Color] -> Color #

lighter :: Double -> Color -> Color #

darker :: Double -> Color -> Color #

brighter :: Double -> Color -> Color #

duller :: Double -> Color -> Color #

assortedColors :: [Color] #

An infinite list of colors.

hue :: Color -> Double #

saturation :: Color -> Double #

luminosity :: Color -> Double #

alpha :: Color -> Double #

Events

data Event #

An event initiated by the user.

Values of this type represent events that the user triggers when using an interactive program.

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 # 
Instance details

Defined in CodeWorld.Event

Methods

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

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

Read Event # 
Instance details

Defined in CodeWorld.Event

Methods

readsPrec :: Int -> ReadS Event

readList :: ReadS [Event]

readPrec :: ReadPrec Event

readListPrec :: ReadPrec [Event]

Show Event # 
Instance details

Defined in CodeWorld.Event

Methods

showsPrec :: Int -> Event -> ShowS

show :: Event -> String

showList :: [Event] -> ShowS

Debugging

trace :: Text -> a -> a #

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 sets appropriate buffering to use the CodeWorld console.