Color-0.1.3.1: Color spaces and conversions between them

Copyright(c) Alexey Kuleshevich 2018-2019
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Graphics.Color.Algebra.Binary

Description

 
Synopsis

Documentation

data Bit Source #

Under the hood, binary pixels are backed by Word8, but can only take values of 0 or 1. Use zero/one to construct a bit and on/off to construct a binary pixel.

Instances
Eq Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

Methods

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

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

Num Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

Methods

(+) :: Bit -> Bit -> Bit #

(-) :: Bit -> Bit -> Bit #

(*) :: Bit -> Bit -> Bit #

negate :: Bit -> Bit #

abs :: Bit -> Bit #

signum :: Bit -> Bit #

fromInteger :: Integer -> Bit #

Ord Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

Methods

compare :: Bit -> Bit -> Ordering #

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

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

(>) :: Bit -> Bit -> Bool #

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

max :: Bit -> Bit -> Bit #

min :: Bit -> Bit -> Bit #

Show Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Storable Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

Methods

sizeOf :: Bit -> Int #

alignment :: Bit -> Int #

peekElemOff :: Ptr Bit -> Int -> IO Bit #

pokeElemOff :: Ptr Bit -> Int -> Bit -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bit #

pokeByteOff :: Ptr b -> Int -> Bit -> IO () #

peek :: Ptr Bit -> IO Bit #

poke :: Ptr Bit -> Bit -> IO () #

Bits Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

Methods

(.&.) :: Bit -> Bit -> Bit #

(.|.) :: Bit -> Bit -> Bit #

xor :: Bit -> Bit -> Bit #

complement :: Bit -> Bit #

shift :: Bit -> Int -> Bit #

rotate :: Bit -> Int -> Bit #

zeroBits :: Bit #

bit :: Int -> Bit #

setBit :: Bit -> Int -> Bit #

clearBit :: Bit -> Int -> Bit #

complementBit :: Bit -> Int -> Bit #

testBit :: Bit -> Int -> Bool #

bitSizeMaybe :: Bit -> Maybe Int #

bitSize :: Bit -> Int #

isSigned :: Bit -> Bool #

shiftL :: Bit -> Int -> Bit #

unsafeShiftL :: Bit -> Int -> Bit #

shiftR :: Bit -> Int -> Bit #

unsafeShiftR :: Bit -> Int -> Bit #

rotateL :: Bit -> Int -> Bit #

rotateR :: Bit -> Int -> Bit #

popCount :: Bit -> Int #

Unbox Bit Source #

Unboxing of a Bit.

Instance details

Defined in Graphics.Color.Algebra.Binary

Elevator Bit Source #

Values: 0 and 1

Instance details

Defined in Graphics.Color.Algebra.Binary

Vector Vector Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

MVector MVector Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

newtype Vector Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

newtype MVector s Bit Source # 
Instance details

Defined in Graphics.Color.Algebra.Binary

newtype MVector s Bit = MV_Bit (MVector s Word8)

toBool :: Bit -> Bool Source #

Convert Bit to Bool

Since: 0.1.0

fromBool :: Bool -> Bit Source #

Convert Bool to Bit

Since: 0.1.0

toNum :: Num a => Bit -> a Source #

Convert a bit to a number.

Since: 0.1.0

fromNum :: (Eq a, Num a) => a -> Bit Source #

Convert a number to a bit. Any non-zero number corresponds to 1.

Since: 0.1.0