Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- drawingOf :: Picture -> IO ()
- animationOf :: (Double -> Picture) -> IO ()
- activityOf :: 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 ()
- interactionOf :: 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
- pictures :: [Picture] -> Picture
- (<>) :: Semigroup a => a -> a -> a
- (&) :: Picture -> Picture -> Picture
- coordinatePlane :: HasCallStack => Picture
- codeWorldLogo :: HasCallStack => Picture
- type Point = (Double, Double)
- translatedPoint :: Double -> Double -> Point -> Point
- rotatedPoint :: 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 :: Double -> Color
- grey :: Double -> Color
- mixed :: Color -> 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
- data MouseButton
- pattern PointerPress :: Point -> Event
- pattern PointerRelease :: Point -> Event
- pattern PointerMovement :: Point -> Event
- trace :: Text -> a -> a
Entry points
Draws a Picture
. This is the simplest CodeWorld entry point.
Shows an animation, with a picture for each time given by the parameter.
:: 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 () |
Runs an interactive CodeWorld program that responds to events. Activities can interact with the user, change over time, and remember information about the past.
:: Int | The number of participants to expect. The participants will be ^ numbered starting at 0. |
-> StaticPtr (StdGen -> world) | The 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.
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 () |
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 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 () |
Runs an interactive event-driven CodeWorld program. This is a generalization of simulations that can respond to events like key presses and mouse movement.
:: 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 () |
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 () |
A version of collaborationOf
that avoids static pointers, and does not
check for consistent parameters.
Pictures
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 2019.
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 2019.
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.
styledText :: HasCallStack => TextStyle -> Font -> Text -> Picture Source #
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.
rotated :: HasCallStack => Double -> Picture -> Picture Source #
A picture rotated by this angle.
Angles are in radians.
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.
vectorLength :: Vector -> Double Source #
vectorDirection :: Vector -> Double Source #
Colors
aquamarine :: Color Source #
chartreuse :: Color Source #
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 | |
MousePress !MouseButton !Point | Warning: Please use PointerPress instead of MousePress.MousePress may be removed July 2019. |
MouseRelease !MouseButton !Point | Warning: Please use PointerRelease instead of MouseRelease.MouseRelease may be removed July 2019. |
MouseMovement !Point | Warning: Please use PointerMovement instead of MouseMovement.MouseMovement may be removed July 2019. |
TimePassing !Double |
data MouseButton Source #
Warning: Please use pointer events, which don't have buttons.MouseButton may be removed July 2019.
Instances
Eq MouseButton Source # | |
Defined in CodeWorld.Event (==) :: MouseButton -> MouseButton -> Bool # (/=) :: MouseButton -> MouseButton -> Bool # | |
Read MouseButton Source # | |
Defined in CodeWorld.Event readsPrec :: Int -> ReadS MouseButton # readList :: ReadS [MouseButton] # readPrec :: ReadPrec MouseButton # readListPrec :: ReadPrec [MouseButton] # | |
Show MouseButton Source # | |
Defined in CodeWorld.Event showsPrec :: Int -> MouseButton -> ShowS # show :: MouseButton -> String # showList :: [MouseButton] -> ShowS # |
pattern PointerPress :: Point -> Event Source #
pattern PointerRelease :: Point -> Event Source #
pattern PointerMovement :: Point -> Event Source #