codeworld-api-0.4.0: Graphics library for CodeWorld

Safe HaskellNone
LanguageHaskell98

CodeWorld.Reflex

Contents

Description

Module for using CodeWorld pictures in Reflex-based FRP applications.

Synopsis

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, PerformEvent t m, MonadIO (Performable m), Adjustable 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.

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, MonadHold t m, MonadFix m, PerformEvent t m, Adjustable t m, MonadIO (Performable m), PostBuild t 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

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

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

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.

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

A rendering of text characters.

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

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 #

assortedColors :: [Color] Source #

An infinite list of colors.