gloss-raster-massiv-0.1.1.5: Massiv-based alternative for gloss-raster
Copyright(c) Matthew Mosior 2023
LicenseBSD-style
Maintainermattm.github@gmail.com
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.Gloss.Raster.Massiv.Internal

Description

WARNING

This module is considered internal.

The Package Versioning Policy does not apply.

The contents of this module may change in any way whatsoever and without any warning between minor versions of this package.

Authors importing this library are expected to track development closely.

All credit goes to the author(s)/maintainer(s) of the containers library for the above warning text.

Description

This library utilizes massiv's superb performance characteristics to supply alternative rasterization functionality to that which is provided by the gloss-raster package.

Synopsis

Graphics.Gloss.Raster.Array Replacement functions - INTERNAL

data ColorMassiv Source #

Custom Color data type.

Constructors

RGBA !Float !Float !Float !Float 

Instances

Instances details
Data ColorMassiv Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

Methods

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

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

toConstr :: ColorMassiv -> Constr #

dataTypeOf :: ColorMassiv -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ColorMassiv Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

Associated Types

type Rep ColorMassiv :: Type -> Type #

Num ColorMassiv Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

Show ColorMassiv Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

GStorable ColorMassiv Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

Eq ColorMassiv Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

type Rep ColorMassiv Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

data RGBTriplet Source #

Custom data type for makeFrame function in Graphics.Gloss.Raster.Field.

Constructors

RGBTriplet Word8 Word8 Word8 

Instances

Instances details
Data RGBTriplet Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

Methods

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

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

toConstr :: RGBTriplet -> Constr #

dataTypeOf :: RGBTriplet -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic RGBTriplet Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

Associated Types

type Rep RGBTriplet :: Type -> Type #

Show RGBTriplet Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

GStorable RGBTriplet Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

Eq RGBTriplet Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

type Rep RGBTriplet Source # 
Instance details

Defined in Graphics.Gloss.Raster.Massiv.Internal

type Rep RGBTriplet = D1 ('MetaData "RGBTriplet" "Graphics.Gloss.Raster.Massiv.Internal" "gloss-raster-massiv-0.1.1.5-inplace" 'False) (C1 ('MetaCons "RGBTriplet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8))))

rgbMassiv :: Float -> Float -> Float -> ColorMassiv Source #

Construct a color from red, green, blue components.

Each component is clamped to the range [0..1]

rgbMassivI :: Int -> Int -> Int -> ColorMassiv Source #

Construct a color from red, green, blue components.

Each component is clamped to the range [0..255]

rgbMassiv8w :: Word8 -> Word8 -> Word8 -> ColorMassiv Source #

Construct a color from red, green, blue components.

rgbMassiv' :: Float -> Float -> Float -> ColorMassiv Source #

Like rgb, but take pre-clamped components for speed.

If you're building a new color for every pixel then use this version, however if your components are out of range then the picture you get will be implementation dependent.

rgbMassivI' :: Int -> Int -> Int -> ColorMassiv Source #

Like rgbI, but take pre-clamped components for speed.

If you're building a new color for every pixel then use this version, however if your components are out of range then the picture you get will be implementation dependent.

makeColorMassiv Source #

Arguments

:: Float

Red component.

-> Float

Green component.

-> Float

Blue component.

-> Float

Alpha component.

-> ColorMassiv 

Make a custom color. All components are clamped to the range [0..1].

makeColorMassivI :: Int -> Int -> Int -> Int -> ColorMassiv Source #

Make a custom color. All components are clamped to the range [0..255].

makeRawColorMassiv :: Float -> Float -> Float -> Float -> ColorMassiv Source #

Make a custom color.

Using this function over makeColor avoids clamping the components, which saves time. However, if the components are out of range then this will result in integer overflow at rendering time, and the actual picture you get will be implementation dependent.

You'll only need to use this function when using the gloss-raster package that builds a new color for every pixel. If you're just working with the Picture data type then it there is no need for raw colors.

makeRawColorMassivI :: Int -> Int -> Int -> Int -> ColorMassiv Source #

Make a custom color, taking pre-clamped components.

rgbaOfColorMassiv :: ColorMassiv -> (Float, Float, Float, Float) Source #

Take the RGBA components of a color.