processing-for-haskell-0.1.0.0: Computer graphics for kids and artists with Processing implemented in Haskell.

Safe HaskellNone
LanguageHaskell2010

Graphics.Proc

Contents

Description

Imperative EDSL for graphics and animation. The libary implements a Processing in Haskell.

An example:

import Graphics.Proc

main = runProc $ def { procSetup = setup, procDraw = draw, procUpdate = update }

setup = do
	size (300, 300)
	return 0

draw x = do	
	background (grey 255)
	fill (rgb 0 255 0)
	circle 20 (150 + 50 * sin x, 150)

update x = return (x + 0.1)

We can find the quickstart guide and lots of examples in the project repository on github https://github.com/anton-k/processing-for-haskell (see the directory examples).

Synopsis

Structure

data Proc s Source #

It holds all processing standard callbacks. With it we can set the setup, draw, and update functions. Here we can specify how to react on user-input.

All functions update the program state. They take it in as an argument and produce as result. In Haskell we can not manipulate global variables with such ease as Processing provides. So we have to find out another way to update the state. The natural way for Haskell is to keep the things as explicit as possible. That leads to the following decisions:

  • setup returns the initial state.
  • draw takes the state as an argument and draws it.
  • update should take in the current state and return back the next state.
  • All input processing functions also manipulate the state explicitly by passing arguments.

Notice that the processing function draw is split on two functions: draw and update. The draw is only for drawing the program state and update is for state update.

There is a useful function procUpdateTime that provides a time interval that has passed since the previous update of the state. It can be useful for physics engines.

Instances

Default (Proc s) Source # 

Methods

def :: Proc s #

runProc :: Proc s -> IO () Source #

The main function for rendering processing actions. It sets the scene and starts the rendering of animation.

Types

data Pio a Source #

Processing IO-monad. It has the same meaning as the Haskell IO-monad but it's augmented with Processing library functions.

We can use liftIO to execute ordinary Haskell IO-actions. The Pio has instance for class MonadIO.

text <- liftIO $ readFile filename

Instances

Monad Pio Source # 

Methods

(>>=) :: Pio a -> (a -> Pio b) -> Pio b #

(>>) :: Pio a -> Pio b -> Pio b #

return :: a -> Pio a #

fail :: String -> Pio a #

Functor Pio Source # 

Methods

fmap :: (a -> b) -> Pio a -> Pio b #

(<$) :: a -> Pio b -> Pio a #

Applicative Pio Source # 

Methods

pure :: a -> Pio a #

(<*>) :: Pio (a -> b) -> Pio a -> Pio b #

(*>) :: Pio a -> Pio b -> Pio b #

(<*) :: Pio a -> Pio b -> Pio a #

MonadIO Pio Source # 

Methods

liftIO :: IO a -> Pio a #

type Draw = Pio () Source #

An alias for processing procedures.

type Update s = s -> Pio s Source #

A alias for value update inside processing IO-monad.

type TimeInterval = Float Source #

Time duration in seconds.

data Col Source #

Color datatype. It contains values for three components of the color and transparency. All values range in the interval from 0 to 1.

Constructors

Col Float Float Float Float 

Instances

Show Col Source # 

Methods

showsPrec :: Int -> Col -> ShowS #

show :: Col -> String #

showList :: [Col] -> ShowS #

Default Col Source # 

Methods

def :: Col #

type P2 = (Float, Float) Source #

2D vector.

type P3 = (Float, Float, Float) Source #

3D vector.

Environment

winSize :: Pio P2 Source #

Return the pair of width and height as a 2D vector.

winWidth :: Pio Float Source #

System variable that stores the width of the display window. This value is set by the first parameter of the size() function. For example, the function call size(320, 240) sets the width variable to the value 320. The value of width defaults to 100 if size() is not used in a program.

processing docs: https://processing.org/reference/width.html

winHeight :: Pio Float Source #

System variable that stores the height of the display window. This value is set by the second parameter of the winSize() function. For example, the function call winSize(320, 240) sets the height variable to the value 240. The value of height defaults to 100 if winSize() is not used in a program.

processing docs: https://processing.org/reference/height.html

size :: P2 -> Draw Source #

Defines the dimension of the display window width and height in units of pixels. In a program that has the setup() function, the size() function must be the first line of code inside setup().

processing docs: https://processing.org/reference/size_.html

smooth :: Draw Source #

Draws all geometry with smooth (anti-aliased) edges. This behavior is the default, so smooth() only needs to be used when a program needs to set the smoothing in a different way. The level parameter increases the level of smoothness. This is the level of over sampling applied to the graphics buffer.

processing docs: https://processing.org/reference/smooth_.html

noSmooth :: Pio () Source #

Draws all geometry and fonts with jagged (aliased) edges and images when hard edges between the pixels when enlarged rather than interpoloating pixels. Note that smooth() is active by default, so it is necessary to call noSmooth() to disable smoothing of geometry, fonts, and images.

processing docs: https://processing.org/reference/noSmooth_.html

frameCount :: Pio Int Source #

The system variable frameCount contains the number of frames that have been displayed since the program started. Inside setup() the value is 0, after the first iteration of draw it is 1, etc.

processing docs: https://processing.org/reference/frameCount.html

frameRate :: Float -> Pio () Source #

Specifies the number of frames to be displayed every second. For example, the function call frameRate(30) will attempt to refresh 30 times a second. If the processor is not fast enough to maintain the specified rate, the frame rate will not be achieved. Setting the frame rate within setup() is recommended. The default rate is 60 frames per second.

processing docs: https://processing.org/reference/frameRate_.html

loop :: Draw Source #

By default, Processing loops through draw() continuously, executing the code within it. However, the draw() loop may be stopped by calling noLoop(). In that case, the draw() loop can be resumed with loop().

processing docs: https://processing.org/reference/loop_.html

noLoop :: Draw Source #

Stops Processing from continuously executing the code within draw(). If loop() is called, the code in draw() begins to run continuously again. If using noLoop() in setup(), it should be the last line inside the block.

processing docs: https://processing.org/reference/noLoop_.html

redraw :: Draw Source #

Executes the code within draw() one time. This functions allows the program to update the display window only when necessary, for example when an event registered by mousePressed() or keyPressed() occurs.

In structuring a program, it only makes sense to call redraw() within events such as mousePressed(). This is because redraw() does not run draw() immediately (it only sets a flag that indicates an update is needed).

processing docs: https://processing.org/reference/redraw_.html

Data

We can use ordinary Haskell datatypes primitive and composite ones.

Conversion

float :: Int -> Float Source #

Converts ints to floats.

int :: Float -> Int Source #

Converts floats to ints.

String Functions

We can use standard Haskell string functions.

Array Functions

Control

We can use plain old Bool datatype.

Shape

2D Primitives

triangle :: P2 -> P2 -> P2 -> Draw Source #

A triangle is a plane created by connecting three points.

processing docs: https://processing.org/reference/triangle_.html

rect :: P2 -> P2 -> Draw Source #

Draws a rectangle to the screen. A rectangle is a four-sided shape with every angle at ninety degrees. By default, the first two parameters set the location of the upper-left corner, the third sets the width, and the fourth sets the height. The way these parameters are interpreted, however, may be changed with the rectMode() function.

processing docs: https://processing.org/reference/rect_.html

quad :: P2 -> P2 -> P2 -> P2 -> Draw Source #

A quad is a quadrilateral, a four sided polygon. It is similar to a rectangle, but the angles between its edges are not constrained to ninety degrees. The first pair of parameters (x1,y1) sets the first vertex and the subsequent pairs should proceed clockwise or counter-clockwise around the defined shape.

processing docs: https://processing.org/reference/quad_.html

ellipse :: P2 -> P2 -> Draw Source #

Draws an ellipse (oval) to the screen. An ellipse with equal width and height is a circle. By default, the first two parameters set the location, and the third and fourth parameters set the shape's width and height. The origin may be changed with the ellipseMode() function.

processing docs: https://processing.org/reference/ellipse_.html

circle :: Float -> P2 -> Draw Source #

Draws a circle with a given radius and center.

circle radius center

line :: P2 -> P2 -> Draw Source #

Draws a line (a direct path between two points) to the screen.

processing docs: https://processing.org/reference/line_.html

linePath :: [P2] -> Draw Source #

Draws a line-path (sequence of line segments).

point :: P2 -> Draw Source #

Draws a point, a coordinate in space at the dimension of one pixel.

processing docs: https://processing.org/reference/point_.html

pointPath :: [P2] -> Draw Source #

Draws a sequence of points.

polygon :: [P2] -> Draw Source #

Draws a polygon.

Curves

bezier :: P2 -> P2 -> P2 -> P2 -> Draw Source #

Draws a Bezier curve on the screen. These curves are defined by a series of anchor and control points. The first two parameters specify the first anchor point and the last two parameters specify the other anchor point. The middle parameters specify the control points which define the shape of the curve. Bezier curves were developed by French engineer Pierre Bezier.

processing docs: https://processing.org/reference/bezier_.html

3D Primitives

Attributes

type EllipseMode = DrawMode Source #

Modes for drawing of ellipse. See ellipseMode.

type RectMode = DrawMode Source #

Modes for drawing of rectangle. See rectMode.

ellipseMode :: EllipseMode -> Draw Source #

Modifies the location from which ellipses are drawn by changing the way in which parameters given to ellipse() are intepreted.

The default mode is ellipseMode Center, which interprets the first two parameters of ellipse() as the shape's center point, while the third and fourth parameters are its width and height.

ellipseMode Radius also uses the first two parameters of ellipse() as the shape's center point, but uses the third and fourth parameters to specify half of the shapes's width and height.

ellipseMode Corner interprets the first two parameters of ellipse() as the upper-left corner of the shape, while the third and fourth parameters are its width and height.

ellipseMode Corners interprets the first two parameters of ellipse() as the location of one corner of the ellipse's bounding box, and the third and fourth parameters as the location of the opposite corner.

rectMode :: RectMode -> Draw Source #

Modifies the location from which rectangles are drawn by changing the way in which parameters given to rect() are intepreted.

The default mode is rectMode Corner, which interprets the first two parameters of rect() as the upper-left corner of the shape, while the third and fourth parameters are its width and height.

rectMode Corners interprets the first two parameters of rect() as the location of one corner, and the third and fourth parameters as the location of the opposite corner.

rectMode Center interprets the first two parameters of rect() as the shape's center point, while the third and fourth parameters are its width and height.

rectMode Radius also uses the first two parameters of rect() as the shape's center point, but uses the third and fourth parameters to specify half of the shapes's width and height.

processing docs: https://processing.org/reference/rectMode_.html

strokeWeight :: Float -> Draw Source #

Sets the width of the stroke used for lines, points, and the border around shapes. All widths are set in units of pixels.

processing docs: https://processing.org/reference/strokeWelight_.html

Vertex

Loading & Displaying

Input

Mouse

mouse :: Pio P2 Source #

Contains coordinates of the mouse as a vector.

mouseX :: Pio Float Source #

The system variable mouseX always contains the current horizontal coordinate of the mouse.

processing docs: https://processing.org/reference/mouseX.html

mouseY :: Pio Float Source #

The system variable mouseX always contains the current vertical coordinate of the mouse.

processing docs: https://processing.org/reference/mouseY.html

relMouse :: Pio P2 Source #

Contains relative coordinates of the mouse as a vector.

relMouseX :: Pio Float Source #

Contains relative mouseX coordinates of the mouse (scaled to the interval [0, 1]).

relMouseY :: Pio Float Source #

Contains relative mouseY coordinates of the mouse (scaled to the interval [0, 1]).

Keyboard

data Key :: * #

A generalized view of keys

Instances

Eq Key 

Methods

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

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

Ord Key 

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

data SpecialKey :: * #

Special keys

Constructors

KeyF1 
KeyF2 
KeyF3 
KeyF4 
KeyF5 
KeyF6 
KeyF7 
KeyF8 
KeyF9 
KeyF10 
KeyF11 
KeyF12 
KeyLeft 
KeyUp 
KeyRight 
KeyDown 
KeyPageUp 
KeyPageDown 
KeyHome 
KeyEnd 
KeyInsert 
KeyNumLock 
KeyBegin 
KeyDelete 
KeyShiftL 
KeyShiftR 
KeyCtrlL 
KeyCtrlR 
KeyAltL 
KeyAltR 
KeyUnknown Int

You should actually never encounter this value, it is just here as a safeguard against future changes in the native GLUT library.

key :: Pio Key Source #

Returns last pressed key.

processing docs: https://processing.org/reference/key.html

modifiers :: Pio Modifiers Source #

Returns last pressed key modifier.

Files

Time & Date

year :: Pio Int Source #

The year() function returns the current year as an integer (2003, 2004, 2005, etc).

processing docs: https://processing.org/reference/year_.html

month :: Pio Int Source #

The month() function returns the current month as a value from 1 - 12.

processing docs: https://processing.org/reference/month_.html

day :: Pio Int Source #

The day() function returns the current day as a value from 1 - 31.

processing docs: https://processing.org/reference/day_.html

hour :: Pio Int Source #

The hour() function returns the current hour as a value from 0 - 23.

processing docs: https://processing.org/reference/hour_.html

minute :: Pio Int Source #

The minute() function returns the current minute as a value from 0 - 59.

processing docs: https://processing.org/reference/minute_.html

second :: Pio Int Source #

The second() function returns the current second as a value from 0 - 59.

processing docs: https://processing.org/reference/second_.html

millis :: Pio Int Source #

Returns the number of milliseconds (thousandths of a second) since starting the program. This information is often used for timing events and animation sequences.

processing docs: https://processing.org/reference/millis_.html

utcHour :: Pio Int Source #

Returens univeral hour.

Output

Text Area

println :: Show a => a -> Pio () Source #

Prints values on the console.

Image

Files

Transform

translate :: P2 -> Draw Source #

Specifies an amount to displace objects within the display window. The x parameter specifies leftright translation, the y parameter specifies updown translation

processing docs: https://processing.org/reference/translate_.html

rotate :: Float -> Draw Source #

Rotates the amount specified by the angle parameter. Angles must be specified in taus (values from 0 to 1)

processing docs: https://processing.org/reference/rotate_.html

rotateX :: Float -> Draw Source #

Rotates around X-axis.

rotateY :: Float -> Draw Source #

Rotates around Y-axis.

rotateZ :: Float -> Draw Source #

Rotates around Z-axis.

scale :: P2 -> Draw Source #

Increases or decreases the size of a shape by expanding and contracting vertices. Objects always scale from their relative origin to the coordinate system. Scale values are specified as decimal percentages. For example, the function call scale(2.0) increases the dimension of a shape by 200%.

processing docs: https://processing.org/reference/scale_.html

resetMatrix :: Draw Source #

Replaces the current matrix with the identity matrix. The equivalent function in OpenGL is glLoadIdentity().

processing docs: https://processing.org/reference/resetMatrix_.html

local :: Draw -> Draw Source #

Applies local transformation. Substitutes the pair of pushMatrix and popMatrix. It can be used like this:

local $ do
  rotate angle
  translate p1
  drawShape params

see https://processing.org/reference/pushMatrix_.html and https://processing.org/reference/popMatrix_.html

applyMatrix :: [Float] -> Draw Source #

Multiplies the current matrix by the one specified through the parameters. This is very slow because it will try to calculate the inverse of the transform, so avoid it whenever possible. The equivalent function in OpenGL is glMultMatrix().

processing docs: https://processing.org/reference/applyMatrix_.html

shearX :: Float -> Draw Source #

Shears a shape around the x-axis the amount specified by the angle parameter. A

processing docs: https://processing.org/reference/shearX_.html

shearY :: Float -> Draw Source #

Shears a shape around the y-axis the amount specified by the angle parameter. A

processing docs: https://processing.org/reference/shearY_.html

Lights

Camera

Coordinates

Material Properties

Color

fill :: Col -> Draw Source #

Sets the color used to fill shapes. For example, if you run fill (rgb 204 102 0), all subsequent shapes will be filled with orange.

processing docs: https://processing.org/reference/fill_.html

noFill :: Draw Source #

Disables filling geometry. If both noStroke() and noFill() are called, nothing will be drawn to the screen.

processing docs: https://processing.org/reference/noFill_.html

stroke :: Col -> Draw Source #

Sets the color used to draw lines and borders around shapes.

processing docs: https://processing.org/reference/stroke_.html

noStroke :: Draw Source #

Disables drawing the stroke (outline). If both noStroke() and noFill() are called, nothing will be drawn to the screen

processing docs: https://processing.org/reference/noStroke_.html

strokeFill :: Col -> Draw Source #

Sets stroke and fill to the same color.

rgb :: Float -> Float -> Float -> Col Source #

Creates an RGB-color from three values. The values are from 0 to 255.

rgba :: Float -> Float -> Float -> Float -> Col Source #

Creates an RGB-color with transparency.

grey :: Float -> Col Source #

Creates a grey value out of single float value. The value is from 0 to 255.

greya :: Float -> Float -> Col Source #

Creates an grey-color with transparency.

background :: Col -> Draw Source #

The background() function sets the color used for the background of the Processing window. The default background is light gray. This function is typically used within draw() to clear the display window at the beginning of each frame, but it can be used inside setup() to set the background on the first frame of animation or if the backgound need only be set once.

processing docs: https://processing.org/reference/background_.html

clear :: Draw Source #

Clears the pixels within a buffer.

processing docs: https://processing.org/reference/clear_.html

white :: Col Source #

White color.

black :: Col Source #

Black color.

navy :: Col Source #

Nave color.

blue :: Col Source #

Blue color.

aqua :: Col Source #

Aqua color.

teal :: Col Source #

Teal color.

olive :: Col Source #

Olive color.

green :: Col Source #

Green color.

lime :: Col Source #

Lime color.

yellow :: Col Source #

Yellow color.

orange :: Col Source #

Orange color

red :: Col Source #

Red color

maroon :: Col Source #

Maroon color.

fushsia :: Col Source #

Fuchsia color.

purple :: Col Source #

Purple color

gray :: Col Source #

Gray color.

silver :: Col Source #

Silver color.

Image

Loading & Displaying

Textures

Pixels

Rendering

Shaders

Typography

Loading & Displaying

Attributes

Metrics

Math

Operators

Bitwise Operators

Calculation

remap :: FloatInterval -> FloatInterval -> Float -> Float Source #

Re-maps a number from one range to another. Originally called map in the Processing, but in Haskell this name is already taken.

processing docs: https://processing.org/reference/map_.html

type FloatInterval = (Float, Float) Source #

Interval for float value (minValue, maxValue).

constrain :: (Float, Float) -> Float -> Float Source #

Constrains a value to not exceed a maximum and minimum value.

processing docs: https://processing.org/reference/constrain_.html

constrain2 :: (P2, P2) -> P2 -> P2 Source #

The constrian that is defined on vectors.

Trigonometry

radians :: Float -> Float Source #

Converts degrees to radians.

degrees :: Float -> Float Source #

Converts rdians to degrees.

e :: Float -> P2 Source #

Converts angle in taus to unit vector rotated by given angle.

erad :: Float -> P2 Source #

The function e in radians.

Random

randomSeed :: Int -> Pio () Source #

Sets the seed value for random(). By default, random() produces different results each time the program is run. Set the seed parameter to a constant to return the same pseudo-random numbers each time the software is run.

processing docs: https://processing.org/reference/randomSeed_.html

random :: Float -> Pio Float Source #

Generates random numbers. Each time the random() function is called, it returns an unexpected value within the specified range. If only one parameter is passed to the function, it will return a float between zero and the value of the high parameter. For example, random(5) returns values between 0 and 5 (starting at zero, and up to, but not including, 5).

processing docs: https://processing.org/reference/random_.html

random2 :: (Float, Float) -> Pio Float Source #

Genrates random numbers within the given range.

randomP2 :: Pio P2 Source #

Creates random point within the ranges of the size of the screen.

randomCol :: Pio Col Source #

Creates random color.

randomCola :: Pio Col Source #

Creates random color with transparency.

randomGaussian :: Pio Float Source #

Returns a float from a random series of numbers having a mean of 0 and standard deviation of 1. Each time the randomGaussian() function is called, it returns a number fitting a Gaussian, or normal, distribution. There is theoretically no minimum or maximum value that randomGaussian() might return. Rather, there is just a very low probability that values far from the mean will be returned; and a higher probability that numbers near the mean will be returned.

processing docs: https://processing.org/reference/randomGaussian_.html

Perlin noise

Returns the Perlin noise value at specified coordinates. Perlin noise is a random sequence generator producing a more natural, harmonic succession of numbers than that of the standard random() function. It was developed by Ken Perlin in the 1980s and has been used in graphical applications to generate procedural textures, shapes, terrains, and other seemingly organic forms.

processing docs: https://processing.org/reference/noise_.html

data NoiseDetail Source #

Parameters for perlin noise. See docs for function noiseDetail.

Instances

noiseDetail :: Int -> Float -> Pio () Source #

Adjusts the character and level of detail produced by the Perlin noise function. Similar to harmonics in physics, noise is computed over several octaves. Lower octaves contribute more to the output signal and as such define the overal intensity of the noise, whereas higher octaves create finer-grained details in the noise sequence.

By default, noise is computed over 4 octaves with each octave contributing exactly half than its predecessor, starting at 50% strength for the first octave. This falloff amount can be changed by adding an additional function parameter. For example, a falloff factor of 0.75 means each octave will now have 75% impact (25% less) of the previous lower octave. While any number between 0.0 and 1.0 is valid, note that values greater than 0.5 may result in noise() returning values greater than 1.0.

By changing these parameters, the signal created by the noise() function can be adapted to fit very specific needs and characteristics.

processing docs: https://processing.org/reference/noiseDetail_.html

noiseOctaves :: Int -> Pio () Source #

Sets the number of octaves for perlin noise.

noiseSeed :: Int -> Pio () Source #

Sets the seed value for noise(). By default, noise() produces different results each time the program is run. Set the seed parameter to a constant to return the same pseudo-random numbers each time the software is run.

processing docs: https://processing.org/reference/noiseSeed_.html

noise1 :: Float -> Pio Float Source #

Returns 1D Perlin noise.

noise2 :: P2 -> Pio Float Source #

Returns 2D Perlin noise.

noise3 :: P3 -> Pio Float Source #

Returns 3D Perlin noise.

Misc

onCircle :: Float -> P2 -> Float -> P2 Source #

Maps values from interval (0, 1) to the points on the circle.

onCircle radius center value

onLine :: P2 -> P2 -> Float -> P2 Source #

Maps values from interval (0, 1) to the points on the line segment.

onLine point1 point2 value

uon :: (Float, Float) -> Float -> Float Source #

Rescales the unipolar scale (0, 1) to the given range.

Pio mutable values

data PioRef a Source #

Datatyp for mutable variables. We can create a reference and then manipulate the value with functions readPioRef and writePioRef. The API is the same as in the case of IORefs. It's standard way to work with mutables in haskell.

Instances

Eq (PioRef a) Source # 

Methods

(==) :: PioRef a -> PioRef a -> Bool #

(/=) :: PioRef a -> PioRef a -> Bool #

newPioRef :: a -> Pio (PioRef a) Source #

Creates a reference for a mutable value. The argument is an initial value assigned to the variable.

readPioRef :: PioRef a -> Pio a Source #

Reads the value from the reference.

writePioRef :: PioRef a -> a -> Pio () Source #

Writes the value to reference.

modifyPioRef :: PioRef a -> (a -> a) -> Pio () Source #

Modifies a value iside the reference with a function.

Useful standard functions

module Data.Cross