Safe Haskell | None |
---|---|
Language | Haskell98 |
Module for using CodeWorld pictures in Reflex-based FRP applications.
Synopsis
- reflexOf :: (forall t m. (Reflex t, MonadHold t m, MonadFix m, TriggerEvent t m, PerformEvent t m, MonadIO m, MonadIO (Performable m), Adjustable t m, NotReady t m, PostBuild t m) => ReactiveInput t -> m (Dynamic t Picture)) -> IO ()
- data ReactiveInput t
- keyPress :: ReactiveInput t -> Event t Text
- keyRelease :: ReactiveInput t -> Event t Text
- textEntry :: ReactiveInput t -> Event t Text
- pointerPress :: ReactiveInput t -> Event t Point
- pointerRelease :: ReactiveInput t -> Event t Point
- pointerPosition :: ReactiveInput t -> Dynamic t Point
- pointerDown :: ReactiveInput t -> Dynamic t Bool
- timePassing :: ReactiveInput t -> Event t Double
- reactiveOf :: (forall t m. ReflexCodeWorld t m => m ()) -> IO ()
- debugReactiveOf :: (forall t m. ReflexCodeWorld t m => m ()) -> IO ()
- class (Reflex t, Adjustable t m, MonadHold t m, NotReady t m, PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadFix m, MonadIO m, MonadIO (Performable m)) => ReflexCodeWorld t m | m -> t
- getKeyPress :: ReflexCodeWorld t m => m (Event t Text)
- getKeyRelease :: ReflexCodeWorld t m => m (Event t Text)
- getTextEntry :: ReflexCodeWorld t m => m (Event t Text)
- getPointerClick :: ReflexCodeWorld t m => m (Event t Point)
- getPointerPosition :: ReflexCodeWorld t m => m (Dynamic t Point)
- isPointerDown :: ReflexCodeWorld t m => m (Dynamic t Bool)
- getTimePassing :: ReflexCodeWorld t m => m (Event t Double)
- draw :: ReflexCodeWorld t m => Dynamic t Picture -> m ()
- data Picture
- blank :: HasCallStack => Picture
- polyline :: HasCallStack => [Point] -> Picture
- thickPolyline :: 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
- lettering :: HasCallStack => Text -> Picture
- data TextStyle
- data Font
- 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 :: 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
- 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
- yellow :: Color
- orange :: 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
Documentation
Using Reflex with CodeWorld
This is an alternative to the standard CodeWorld API, which is based on
the Reflex library. You should import this instead of CodeWorld
, since
the CodeWorld
module exports conflict with Reflex names.
You'll provide a function whose input can be used to access the user's
actions with keys, the mouse pointer, and time, and whose output is a
Picture
. The Picture
value is built with the same combinators as the
main CodeWorld
library.
The Reflex API is documented in many places, but a great reference is available in the Reflex Quick Reference.
The old API consists of the function reflexOf
. WARNING: This API will soon
be deleted in favor of the newer API described below.
A simple example:
import CodeWorld.Reflex import Reflex main :: IO () main = reflexOf $ \input -> do angle <- foldDyn (+) 0 (gate (current (pointerDown input)) (timePassing input)) return $ (uncurry translated <$> pointerPosition input <*>) $ (colored <$> bool red green <$> pointerDown input <*>) $ (rotated <$> angle <*>) $ constDyn (solidRectangle 2 2)
reflexOf :: (forall t m. (Reflex t, MonadHold t m, MonadFix m, TriggerEvent t m, PerformEvent t m, MonadIO m, MonadIO (Performable m), Adjustable t m, NotReady t m, PostBuild t m) => ReactiveInput t -> m (Dynamic t Picture)) -> IO () Source #
Warning: Please use reactiveOf instead of reflexOf.reflexOf will be removed and replaced soon.
The entry point for running Reflex-based CodeWorld programs.
data ReactiveInput t Source #
keyRelease :: ReactiveInput t -> Event t Text Source #
pointerPress :: ReactiveInput t -> Event t Point Source #
pointerRelease :: ReactiveInput t -> Event t Point Source #
pointerPosition :: ReactiveInput t -> Dynamic t Point Source #
pointerDown :: ReactiveInput t -> Dynamic t Bool Source #
timePassing :: ReactiveInput t -> Event t Double Source #
New Entry Point
reactiveOf :: (forall t m. ReflexCodeWorld t m => m ()) -> IO () Source #
Warning: After the current migration is complete,reactiveOf will probably be renamed to reflexOf.
debugReactiveOf :: (forall t m. ReflexCodeWorld t m => m ()) -> IO () Source #
Warning: After the current migration is complete,debugReactiveOf will probably be renamed to debugReflexOf.
class (Reflex t, Adjustable t m, MonadHold t m, NotReady t m, PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadFix m, MonadIO m, MonadIO (Performable m)) => ReflexCodeWorld t m | m -> t Source #
Type class for the builder monad of a CodeWorld/Reflex app.
getKeyPress :: ReflexCodeWorld t m => m (Event t Text) Source #
Gets an Event of key presses. The event value is a logical key name.
getKeyRelease :: ReflexCodeWorld t m => m (Event t Text) Source #
Gets an Event of key presses. The event value is a logical key name.
getTextEntry :: ReflexCodeWorld t m => m (Event t Text) Source #
Gets an Event of text entered. The event value is the typed text.
getPointerClick :: ReflexCodeWorld t m => m (Event t Point) Source #
Gets an event of pointer clicks. The event value is the location of the click.
getPointerPosition :: ReflexCodeWorld t m => m (Dynamic t Point) Source #
Gets the Dynamic position of the pointer.
isPointerDown :: ReflexCodeWorld t m => m (Dynamic t Bool) Source #
Gets a Dynamic indicator whether the pointer is held down.
getTimePassing :: ReflexCodeWorld t m => m (Event t Double) Source #
Gets an Event indicating the passage of time.
draw :: ReflexCodeWorld t m => Dynamic t Picture -> m () Source #
Emits a given Dynamic picture to be drawn to the screen.
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
blank :: HasCallStack => Picture Source #
A blank picture
polyline :: HasCallStack => [Point] -> Picture Source #
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
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.
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))))) |
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.
(&) :: 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)
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)))) |
translucent :: Color -> Color Source #
assortedColors :: [Color] Source #
An infinite list of colors.
saturation :: Color -> Double Source #
luminosity :: Color -> Double Source #