codeworld-api-0.4.0: Graphics library for CodeWorld

Safe HaskellNone
LanguageHaskell98

CodeWorld

Contents

Synopsis

Entry points

drawingOf Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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.

simulationOf Source #

Arguments

:: world

The initial state of the simulation.

-> (Double -> world -> world)

The time step function, which advances the state given the time difference.

-> (world -> Picture)

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

-> IO () 

Warning: Please use activityOf instead of simulationOf.simulationOf may be removed July 2020.

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

debugSimulationOf Source #

Arguments

:: world

The initial state of the simulation.

-> (Double -> world -> world)

The time step function, which advances the state given the time difference.

-> (world -> Picture)

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

-> IO () 

Warning: Please use debugActivityOf instead of debugSimulationOf.debugSimulationOf may be removed July 2020.

interactionOf Source #

Arguments

:: world

The initial state of the interaction.

-> (Double -> world -> world)

The time step function, which advances the state given the time difference.

-> (Event -> world -> world)

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

-> (world -> Picture)

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

-> IO () 

Warning: Please use activityOf instead of interactionOf.interactionOf may be removed July 2020.

Runs an interactive event-driven CodeWorld program. This is a generalization of simulations that can respond to events like key presses and mouse movement.

debugInteractionOf Source #

Arguments

:: world

The initial state of the interaction.

-> (Double -> world -> world)

The time step function, which advances the state given the time difference.

-> (Event -> world -> world)

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

-> (world -> Picture)

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

-> IO () 

Warning: Please use debugActivityOf instead of debugInteractionOf.debugInteractionOf may be removed July 2020.

collaborationOf Source #

Arguments

:: Int

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

-> StaticPtr (StdGen -> world)

The initial state of the collaboration.

-> StaticPtr (Double -> world -> world)

The time step function, which advances the state given the time difference.

-> 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 () 

Warning: Please use groupActivityOf instead of collaborationOf.collaborationOf may be removed July 2020.

Runs an interactive multi-user CodeWorld program, involving multiple participants over the internet.

unsafeCollaborationOf Source #

Arguments

:: Int

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

-> (StdGen -> world)

The initial state of the collaboration.

-> (Double -> world -> world)

The time step function, which advances the state given the time difference.

-> (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 () 

Warning: Please use unsafeGroupActivityOf instead of unsafeCollaborationOf.unsafeCollaborationOf may be removed July 2020.

A version of collaborationOf that avoids static pointers, and does not check for consistent parameters.

Pictures

data Picture Source #

Instances
Generic Picture Source # 
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 Source # 
Instance details

Defined in CodeWorld.Picture

Monoid Picture Source # 
Instance details

Defined in CodeWorld.Picture

NFData Picture Source # 
Instance details

Defined in CodeWorld.Picture

Methods

rnf :: Picture -> () #

type Rep Picture Source # 
Instance details

Defined in CodeWorld.Picture

type Rep Picture = D1 (MetaData "Picture" "CodeWorld.Picture" "codeworld-api-0.4.0-ITbvbNnp6mHHRCEs5dsFXm" 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 "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 Source #

Constructors

Plain 
Bold 
Italic 
Instances
Show TextStyle Source # 
Instance details

Defined in CodeWorld.Picture

Generic TextStyle Source # 
Instance details

Defined in CodeWorld.Picture

Associated Types

type Rep TextStyle :: Type -> Type #

NFData TextStyle Source # 
Instance details

Defined in CodeWorld.Picture

Methods

rnf :: TextStyle -> () #

type Rep TextStyle Source # 
Instance details

Defined in CodeWorld.Picture

type Rep TextStyle = D1 (MetaData "TextStyle" "CodeWorld.Picture" "codeworld-api-0.4.0-ITbvbNnp6mHHRCEs5dsFXm" 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 Source #

Instances
Show Font Source # 
Instance details

Defined in CodeWorld.Picture

Methods

showsPrec :: Int -> Font -> ShowS #

show :: Font -> String #

showList :: [Font] -> ShowS #

Generic Font Source # 
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 Source # 
Instance details

Defined in CodeWorld.Picture

Methods

rnf :: Font -> () #

type Rep Font Source # 
Instance details

Defined in CodeWorld.Picture

type Rep Font = D1 (MetaData "Font" "CodeWorld.Picture" "codeworld-api-0.4.0-ITbvbNnp6mHHRCEs5dsFXm" 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 Source #

A blank picture

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

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

path :: HasCallStack => [Point] -> Picture Source #

Warning: Please use polyline instead of path.path may be removed July 2020.

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

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

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

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

Warning: Please used thickPolyline instead of thickPath.thickPath may be removed July 2020.

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

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

A thin polygon with these points as vertices

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

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

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

A solid polygon with these points as vertices

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

A smooth curve passing through these points.

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

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

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

A smooth closed curve passing through these points.

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

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

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

A solid smooth closed curve passing through these points.

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

A thin rectangle, with this width and height

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

A solid rectangle, with this width and height

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

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

circle :: HasCallStack => Double -> Picture Source #

A thin circle, with this radius

solidCircle :: HasCallStack => Double -> Picture Source #

A solid circle, with this radius

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

A thick circle, with this line width and radius

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

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

Angles are in radians.

sector :: HasCallStack => 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 :: HasCallStack => 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 :: HasCallStack => Text -> Picture Source #

Warning: Please used lettering instead of text.text may be removed July 2020.

A rendering of text characters.

lettering :: HasCallStack => Text -> Picture Source #

A rendering of text characters.

styledText :: HasCallStack => TextStyle -> Font -> Text -> Picture Source #

Warning: Please used styledLettering instead of styledText.styledText may be removed July 2020.

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

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

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

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

A picture drawn entirely in this color.

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

A picture drawn entirely in this colour.

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

A picture drawn translated in these directions.

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

A picture scaled by these factors in the x and y directions.

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

A picture scaled uniformly in all directions by this scale factor.

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

A picture rotated by this angle.

Angles are in radians.

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

An associative operation.

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

Binary composition of pictures.

coordinatePlane :: HasCallStack => Picture Source #

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

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

:: HasCallStack => Picture Source #

The CodeWorld logo.

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

Move given point by given X-axis and Y-axis offsets >>> translatedPoint 1 2 (10,10) (11.0,12.0) >>> translatedPoint (-1) (-2) (0,0) (-1.0,-2.0)

vectorDirection :: Vector -> Double Source #

Given vector, calculate angle in radians that it has with the X-axis.

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

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

Rotate given vector by 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)

Colors

data Color Source #

Constructors

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

Defined in CodeWorld.Color

Methods

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

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

Show Color Source # 
Instance details

Defined in CodeWorld.Color

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 
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 Source # 
Instance details

Defined in CodeWorld.Color

Methods

rnf :: Color -> () #

type Rep Color Source # 
Instance details

Defined in CodeWorld.Color

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

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

cyan :: Color Source #

Warning: Please use HSL(pi, 0.75, 0.5) instead of cyan.The variable cyan may be removed July 2020.

magenta :: Color Source #

Warning: Please use HSL(5 * pi / 3, 0.75, 0.5) instead of magenta.The variable magenta may be removed July 2020.

aquamarine :: Color Source #

Warning: Please use HSL(5 * pi / 6, 0.75, 0.5) instead of aquamarine.The variable aquamarine may be removed July 2020.

azure :: Color Source #

Warning: Please use HSL(7 * pi / 6, 0.75, 0.5) instead of azure.The variable azure may be removed July 2020.

violet :: Color Source #

Warning: Please use purple instead of violet.The variable violet may be removed July 2020.

chartreuse :: Color Source #

Warning: Please use HSL(pi / 2, 0.75, 0.5) instead of chartreuse.The variable chartreuse may be removed July 2020.

rose :: Color Source #

Warning: Please use HSL(11 * pi / 6, 0.75, 0.5) instead of rose.The variable rose may be removed July 2020.

assortedColors :: [Color] Source #

An infinite list of colors.

Events

data Event Source #

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

Defined in CodeWorld.Event

Methods

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

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

Read Event Source # 
Instance details

Defined in CodeWorld.Event

Show Event Source # 
Instance details

Defined in CodeWorld.Event

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