Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- drawingOf :: Picture -> IO ()
- animationOf :: (Double -> Picture) -> IO ()
- activityOf :: world -> (Event -> world -> world) -> (world -> Picture) -> IO ()
- debugActivityOf :: world -> (Event -> world -> world) -> (world -> Picture) -> IO ()
- groupActivityOf :: Int -> StaticPtr (StdGen -> world) -> StaticPtr (Int -> Event -> world -> world) -> StaticPtr (Int -> world -> Picture) -> IO ()
- unsafeGroupActivityOf :: Int -> (StdGen -> world) -> (Int -> Event -> world -> world) -> (Int -> world -> Picture) -> IO ()
- simulationOf :: world -> (Double -> world -> world) -> (world -> Picture) -> IO ()
- debugSimulationOf :: world -> (Double -> world -> world) -> (world -> Picture) -> IO ()
- interactionOf :: world -> (Double -> world -> world) -> (Event -> world -> world) -> (world -> Picture) -> IO ()
- debugInteractionOf :: world -> (Double -> world -> world) -> (Event -> world -> world) -> (world -> Picture) -> IO ()
- collaborationOf :: Int -> StaticPtr (StdGen -> world) -> StaticPtr (Double -> world -> world) -> StaticPtr (Int -> Event -> world -> world) -> StaticPtr (Int -> world -> Picture) -> IO ()
- unsafeCollaborationOf :: Int -> (StdGen -> world) -> (Double -> world -> world) -> (Int -> Event -> world -> world) -> (Int -> world -> Picture) -> IO ()
- data Picture
- data TextStyle
- data Font
- blank :: HasCallStack => Picture
- polyline :: HasCallStack => [Point] -> Picture
- path :: HasCallStack => [Point] -> Picture
- thickPolyline :: HasCallStack => Double -> [Point] -> Picture
- thickPath :: HasCallStack => Double -> [Point] -> Picture
- polygon :: HasCallStack => [Point] -> Picture
- thickPolygon :: HasCallStack => Double -> [Point] -> Picture
- solidPolygon :: HasCallStack => [Point] -> Picture
- curve :: HasCallStack => [Point] -> Picture
- thickCurve :: HasCallStack => Double -> [Point] -> Picture
- closedCurve :: HasCallStack => [Point] -> Picture
- thickClosedCurve :: HasCallStack => Double -> [Point] -> Picture
- solidClosedCurve :: HasCallStack => [Point] -> Picture
- rectangle :: HasCallStack => Double -> Double -> Picture
- solidRectangle :: HasCallStack => Double -> Double -> Picture
- thickRectangle :: HasCallStack => Double -> Double -> Double -> Picture
- circle :: HasCallStack => Double -> Picture
- solidCircle :: HasCallStack => Double -> Picture
- thickCircle :: HasCallStack => Double -> Double -> Picture
- arc :: HasCallStack => Double -> Double -> Double -> Picture
- sector :: HasCallStack => Double -> Double -> Double -> Picture
- thickArc :: HasCallStack => Double -> Double -> Double -> Double -> Picture
- text :: HasCallStack => Text -> Picture
- lettering :: HasCallStack => Text -> Picture
- styledText :: HasCallStack => TextStyle -> Font -> Text -> Picture
- styledLettering :: HasCallStack => TextStyle -> Font -> Text -> Picture
- colored :: HasCallStack => Color -> Picture -> Picture
- coloured :: HasCallStack => Color -> Picture -> Picture
- translated :: HasCallStack => Double -> Double -> Picture -> Picture
- scaled :: HasCallStack => Double -> Double -> Picture -> Picture
- dilated :: HasCallStack => Double -> Picture -> Picture
- rotated :: HasCallStack => Double -> Picture -> Picture
- reflected :: HasCallStack => Double -> Picture -> Picture
- clipped :: HasCallStack => Double -> Double -> Picture -> Picture
- pictures :: HasCallStack => [Picture] -> Picture
- (<>) :: Semigroup a => a -> a -> a
- (&) :: HasCallStack => Picture -> Picture -> Picture
- coordinatePlane :: HasCallStack => Picture
- codeWorldLogo :: HasCallStack => Picture
- type Point = (Double, Double)
- translatedPoint :: Double -> Double -> Point -> Point
- rotatedPoint :: Double -> Point -> Point
- reflectedPoint :: Double -> Point -> Point
- scaledPoint :: Double -> Double -> Point -> Point
- dilatedPoint :: Double -> Point -> Point
- type Vector = (Double, Double)
- vectorLength :: Vector -> Double
- vectorDirection :: Vector -> Double
- vectorSum :: Vector -> Vector -> Vector
- vectorDifference :: Vector -> Vector -> Vector
- scaledVector :: Double -> Vector -> Vector
- rotatedVector :: Double -> Vector -> Vector
- dotProduct :: Vector -> Vector -> Double
- data Color = RGBA !Double !Double !Double !Double
- type Colour = Color
- pattern RGB :: Double -> Double -> Double -> Color
- pattern HSL :: Double -> Double -> Double -> Color
- black :: Color
- white :: Color
- red :: Color
- green :: Color
- blue :: Color
- cyan :: Color
- magenta :: Color
- yellow :: Color
- aquamarine :: Color
- orange :: Color
- azure :: Color
- violet :: Color
- chartreuse :: Color
- rose :: Color
- brown :: Color
- pink :: Color
- purple :: Color
- gray :: Color
- grey :: Color
- mixed :: [Color] -> Color
- lighter :: Double -> Color -> Color
- light :: Color -> Color
- darker :: Double -> Color -> Color
- dark :: Color -> Color
- brighter :: Double -> Color -> Color
- bright :: Color -> Color
- duller :: Double -> Color -> Color
- dull :: Color -> Color
- translucent :: Color -> Color
- assortedColors :: [Color]
- hue :: Color -> Double
- saturation :: Color -> Double
- luminosity :: Color -> Double
- alpha :: Color -> Double
- data Event
- = KeyPress !Text
- | KeyRelease !Text
- | PointerPress !Point
- | PointerRelease !Point
- | PointerMovement !Point
- | TextEntry !Text
- | TimePassing !Double
- trace :: Text -> a -> a
Entry points
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
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
:: 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 Event
s.
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
:: 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.
:: 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. |
-> 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 #
:: 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.
:: 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.
:: 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.
:: 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.
:: 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.
:: 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 #
:: 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
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
Plain | Plain letters with no style |
Bold | Heavy, thick lettering used for emphasis |
Italic | Slanted script-like lettering used for emphasis |
Instances
Show TextStyle Source # | |
Generic TextStyle Source # | |
NFData TextStyle Source # | |
Defined in CodeWorld.Picture | |
type Rep TextStyle Source # | |
Defined in CodeWorld.Picture type Rep TextStyle = D1 (MetaData "TextStyle" "CodeWorld.Picture" "codeworld-api-0.5.0-IX5NLBlffw06kJrrEJKtq9" 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))) |
Instances
Show Font Source # | |
Generic Font Source # | |
NFData Font Source # | |
Defined in CodeWorld.Picture | |
type Rep Font Source # | |
Defined in CodeWorld.Picture type Rep Font = D1 (MetaData "Font" "CodeWorld.Picture" "codeworld-api-0.5.0-IX5NLBlffw06kJrrEJKtq9" 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
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
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
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.
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. Scaling by a negative factoralso reflects across that axis.
dilated :: HasCallStack => Double -> Picture -> Picture Source #
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 Source #
A picture rotated by this angle about the origin.
Angles are in radians.
reflected :: HasCallStack => Double -> Picture -> Picture Source #
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 Source #
A picture clipped to a rectangle around the origin with this width and height.
(&) :: 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 = ...
codeWorldLogo :: HasCallStack => Picture Source #
The CodeWorld logo.
type Point = (Double, Double) Source #
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 Source #
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 Source #
Rotates a given point by given angle, in radians
>>>
rotatedPoint 45 (10, 0)
(7.071, 7.071)
reflectedPoint :: Double -> Point -> Point Source #
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 Source #
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 Source #
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)
vectorLength :: Vector -> Double Source #
The length of the given vector.
>>>
vectorLength (10, 10)
14.14
vectorDirection :: Vector -> Double Source #
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
scaledVector :: Double -> Vector -> Vector Source #
Scales a given vector by a given scalar multiplier.
>>>
scaledPoint 2 (10, 10)
(20, 20)
rotatedVector :: Double -> Vector -> Vector Source #
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)
Colors
Instances
Eq Color Source # | |
Show Color Source # | |
Generic Color Source # | |
NFData Color Source # | |
Defined in CodeWorld.Color | |
type Rep Color Source # | |
Defined in CodeWorld.Color type Rep Color = D1 (MetaData "Color" "CodeWorld.Color" "codeworld-api-0.5.0-IX5NLBlffw06kJrrEJKtq9" 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)))) |
Warning: Please use HSL(pi, 0.75, 0.5) instead of cyan.The variable cyan may be removed July 2020.
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.
Warning: Please use HSL(7 * pi / 6, 0.75, 0.5) instead of azure.The variable azure may be removed July 2020.
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.
Warning: Please use HSL(11 * pi / 6, 0.75, 0.5) instead of rose.The variable rose may be removed July 2020.
translucent :: Color -> Color Source #
assortedColors :: [Color] Source #
An infinite list of colors.
saturation :: Color -> Double Source #
luminosity :: Color -> Double Source #
Events
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
KeyPress !Text | |
KeyRelease !Text | |
PointerPress !Point | |
PointerRelease !Point | |
PointerMovement !Point | |
TextEntry !Text | |
TimePassing !Double |