openexr-write-0.1.0.2: Library for writing images in OpenEXR HDR file format.

Copyright(c) 2018 Pavol Klacansky
LicensePublicDomain
Maintainerpavol@klacansky.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Graphics.OpenEXR

Description

Library for writting OpenEXR images which support high dynamic range. These images are common in computer graphics, especially ray tracing, and can be used to delay quantization to the post-processing stage.

An example of writting 1x1 ZIP compressed image consisting of a red pixel.

module Main where

import qualified Data.Vector      as V
import qualified Graphics.OpenEXR as EXR


main :: IO ()
main = do
        let image = EXR.ImageRGBF 1 1 (V.fromList [EXR.PixelRGBF 1.0 0.0 0.0])
        EXR.writeFile "image.exr" image EXR.ZipCompression
Synopsis

Documentation

data Image Source #

Constructors

ImageRGBF 

Fields

Instances
Show Image Source # 
Instance details

Defined in Graphics.OpenEXR

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 
Instance details

Defined in Graphics.OpenEXR

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

NFData Image Source # 
Instance details

Defined in Graphics.OpenEXR

Methods

rnf :: Image -> () #

type Rep Image Source # 
Instance details

Defined in Graphics.OpenEXR

type Rep Image = D1 (MetaData "Image" "Graphics.OpenEXR" "openexr-write-0.1.0.2-Gt37UWOJnEdAX4kM2c9u1N" False) (C1 (MetaCons "ImageRGBF" PrefixI True) (S1 (MetaSel (Just "imageWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "imageHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "imageData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector PixelRGBF)))))

data PixelRGBF Source #

Constructors

PixelRGBF !Float !Float !Float 
Instances
Show PixelRGBF Source # 
Instance details

Defined in Graphics.OpenEXR

Generic PixelRGBF Source # 
Instance details

Defined in Graphics.OpenEXR

Associated Types

type Rep PixelRGBF :: * -> * #

NFData PixelRGBF Source # 
Instance details

Defined in Graphics.OpenEXR

Methods

rnf :: PixelRGBF -> () #

type Rep PixelRGBF Source # 
Instance details

Defined in Graphics.OpenEXR

writeFile :: FilePath -> Image -> CompressionType -> IO () Source #

Write an Image using a CompressionType to an OpenEXR formatted file