ruff-0.4.0.1: relatively useful fractal functions

Copyright(c) Claude Heiland-Allen 20112015
LicenseBSD3
Maintainerclaude@mathr.co.uk
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Fractal.RUFF.Mandelbrot.Image

Description

Generic (slow) functions to render images.

Synopsis

Documentation

simpleImage Source #

Arguments

:: (Ord r, Floating r) 
=> Coordinates r

coordinates

-> Int

max iterations

-> UArray (Int, Int) Bool

image

Render an image with the Simple algorithm. The iteration count is doubled until the image is good enough, or the fixed maximum iteration count is reached.

putStr . unicode $ simpleImage (coordinates 100 100 ((-1.861):+0) (0.001)) 1000000000

complexImage Source #

Arguments

:: (Ord r, Real r, Floating r) 
=> Coordinates r

coordinates

-> Int

max iterations

-> UArray (Int, Int, Channel) Float

image

Render an image with the DistanceEstimate algorithm. The iteration count is doubled until the image is good enough, or the fixed maximum iteration count is reached. The output values are converted to Float.

putStr . unicode . border $ complexImage (coordinates 100 100 ((-1.861):+0) (0.001)) 1000000000

imageLoop Source #

Arguments

:: (Ord r, Floating r) 
=> STRef s Int

escapees

-> a

output array

-> Int

max iterations

-> Int

iterations

-> Bool

prior escapees

-> Int

iterations this phase

-> [Iterate u r]

iterates

-> (Output u r -> ST s ())

output callback

-> ST s a

output array as given

Image rendering loop.

coordinates Source #

Arguments

:: (Ord r, Floating r) 
=> Int

width

-> Int

height

-> Complex r

center

-> r

size

-> Coordinates r 

The parameter plane coordinates for an image, with bounds.

ascii Source #

Arguments

:: UArray (Int, Int) Bool

image

-> String

ascii

Convert a bit array to ascii graphics.

unicode Source #

Arguments

:: UArray (Int, Int) Bool

image

-> String

unicode

Convert a bit array to unicode block graphics.

data Channel Source #

Channels in an image.

Constructors

EscapeTime

continuous dwell

DistanceEstimate'

normalized to pixel spacing

FinalAngle

in [-pi,pi]

Instances

Bounded Channel Source # 
Enum Channel Source # 
Eq Channel Source # 

Methods

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

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

Data Channel Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Channel -> c Channel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Channel #

toConstr :: Channel -> Constr #

dataTypeOf :: Channel -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Channel) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Channel) #

gmapT :: (forall b. Data b => b -> b) -> Channel -> Channel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Channel -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Channel -> r #

gmapQ :: (forall d. Data d => d -> u) -> Channel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Channel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Channel -> m Channel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Channel -> m Channel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Channel -> m Channel #

Ord Channel Source # 
Read Channel Source # 
Show Channel Source # 
Ix Channel Source # 

type Coordinates r = (((Int, Int), (Int, Int)), [(Pair Int Int, Complex r)]) Source #

Image bounds and coordinates.

border Source #

Arguments

:: UArray (Int, Int, Channel) Float

image

-> UArray (Int, Int) Bool 

Convert a distance estimate image to a near-boundary bit array. The input image must have a DistanceEstimate' channel.