{-# LANGUAGE ExistentialQuantification, RankNTypes #-} -- | This module contains the image manipulation primitives of GEGL, called Operations. -- Some of these have defaults, which can be invoked by calling 'Data.Default.def'. -- Those operations with no defaults are marked accordingly. module GEGL.Operation ( Operation(..) , Property(..) , PropertyValue(..) , loadOperation , cropOperation , defaultCropOperation , textOperation , defaultTextOperation -- , defaultFractalExplorerOperation , pngSaveOperation , defaultPNGSaveOperation , checkerboardOperation , defaultCheckerboardOperation , overOperation , defaultOverOperation , bufferSourceOperation , translateOperation , FractalType(..) , FractalMode(..) ) where import Foreign.C.Types import Foreign.C.String import Foreign.Storable(Storable(..)) import Foreign.Ptr (Ptr) import GEGL.FFI.Color (GeglColor(..)) import GEGL.FFI.Buffer (GeglBuffer(..)) import GEGL.Color (Color(..)) import BABL.Format (PixelFormat) data Property = Property { propertyName :: String , propertyValue :: PropertyValue } data PropertyValue = PropertyInt Int | PropertyString String | PropertyDouble Double | PropertyColor Color | PropertyFormat PixelFormat | PropertyBuffer GeglBuffer | PropertyPointer (Ptr ()) data Operation = Operation { operationName :: String , operationParams :: [Property] } -- | Simple Operation to load image files. Is agnostic to image format. -- This operation has no default. loadOperation :: [Property] -> Operation loadOperation = Operation "gegl:load" -- | Operation for cropping a buffer. cropOperation :: [Property] -> Operation cropOperation = Operation "gegl:crop" defaultCropOperation :: Operation defaultCropOperation = cropOperation [] -- | A PNG image saving operation. pngSaveOperation :: [Property] -> Operation pngSaveOperation = Operation "gegl:png-save" defaultPNGSaveOperation :: Operation defaultPNGSaveOperation = pngSaveOperation [] -- | Operation for rendering strings of text. textOperation :: [Property] -> Operation textOperation = Operation "gegl:text" defaultTextOperation :: Operation defaultTextOperation = textOperation [] -- | Layover operation. overOperation :: [Property] -> Operation overOperation = Operation "gegl:over" defaultOverOperation :: Operation defaultOverOperation = overOperation [] -- | Create a checkerboard pattern. checkerboardOperation :: [Property] -> Operation checkerboardOperation = Operation "gegl:checkerboard" defaultCheckerboardOperation :: Operation defaultCheckerboardOperation = checkerboardOperation [] -- | Use an existing 'GeglBuffer' as image source. -- This operation has no default. bufferSourceOperation :: [Property] -> Operation bufferSourceOperation = Operation "gegl:buffer-source" -- | Translate an existing buffer translateOperation :: [Property] -> Operation translateOperation = Operation "gegl:translate" -- | Type for defining the fractal type in 'FractalExplorerOperation'. data FractalType = Mandelbrot | Julia | Barnsley1 | Barnsley2 | Barnsley3 | Spider | ManOWar | Lambda | Sierpinsky -- | Type for defining the color mode in 'FractalExplorerOperation'. data FractalMode = Sine | Cosine | None