{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} -- | -- Module : Graphics.Image.ColorSpace.Binary -- Copyright : (c) Alexey Kuleshevich 2016 -- License : BSD3 -- Maintainer : Alexey Kuleshevich -- Stability : experimental -- Portability : non-portable -- module Graphics.Image.ColorSpace.Binary ( Binary(..), Bit(..), on, off, isOn, isOff, fromBool, module Data.Bits ) where import Prelude hiding (map) import Data.Bits import Data.Word (Word8) import Graphics.Image.Interface import Data.Typeable (Typeable) import Foreign.Ptr import Foreign.Storable -- | This is a Binary colorspace, pixel's of which can be created using -- these __/constructors/__: -- -- [@'on'@] Represents value @1@ or 'True'. It's a foreground pixel and is -- displayed in black. -- -- [@'off'@] Represents value @0@ or 'False'. It's a background pixel and is -- displayed in white. -- -- Note, that values are inverted before writing to or reading from file, since -- grayscale images represent black as a @0@ value and white as @1@ on a -- @[0,1]@ scale. -- -- Binary pixels also behave as binary numbers with a size of 1-bit, for instance: -- -- >>> on + on -- equivalent to: 1 .|. 1 -- -- >>> (on + on) * off -- equivalent to: (1 .|. 1) .&. 0 -- -- >>> (on + on) - on -- -- data Binary = Binary deriving (Eq, Enum, Bounded, Show, Typeable) -- | Under the hood, Binary pixels are represented as 'Word8', but can only take -- values of @0@ or @1@. newtype Bit = Bit Word8 deriving (Ord, Eq, Typeable) data instance Pixel Binary Bit = PixelBinary {-# UNPACK #-} !Bit deriving (Ord, Eq) instance Show (Pixel Binary Bit) where show (PixelBinary (Bit 0)) = "" show _ = "" instance Bits Bit where (.&.) = (*) {-# INLINE (.&.) #-} (.|.) = (+) {-# INLINE (.|.) #-} (Bit 0) `xor` (Bit 0) = Bit 0 (Bit 1) `xor` (Bit 1) = Bit 0 _ `xor` _ = Bit 1 {-# INLINE xor #-} complement (Bit 0) = Bit 1 complement _ = Bit 0 shift !b 0 = b shift _ _ = Bit 0 rotate !b _ = b zeroBits = Bit 0 bit 0 = Bit 1 bit _ = Bit 0 testBit (Bit 1) 0 = True testBit _ _ = False bitSizeMaybe _ = Just 1 bitSize _ = 1 isSigned _ = False popCount (Bit 0) = 0 popCount _ = 1 instance Bits (Pixel Binary Bit) where (.&.) = liftPx2 (.&.) {-# INLINE (.&.) #-} (.|.) = liftPx2 (.|.) {-# INLINE (.|.) #-} xor = liftPx2 xor {-# INLINE xor #-} complement = liftPx complement shift !b !n = liftPx (`shift` n) b rotate !b !n = liftPx (`rotate` n) b zeroBits = promote zeroBits bit = promote . bit testBit (PixelBinary (Bit 1)) 0 = True testBit _ _ = False bitSizeMaybe _ = Just 1 bitSize _ = 1 isSigned _ = False popCount (PixelBinary (Bit 0)) = 0 popCount _ = 1 -- | Represents value 'True' or @1@ in binary. Often also called a foreground -- pixel of an object. on :: Pixel Binary Bit on = PixelBinary (Bit 1) {-# INLINE on #-} -- | Represents value 'False' or @0@ in binary. Often also called a background -- pixel. off :: Pixel Binary Bit off = PixelBinary (Bit 0) {-# INLINE off #-} -- | Convert a 'Bool' to a 'PixelBin' pixel. -- -- >>> isOn (fromBool True) -- True -- fromBool :: Bool -> Pixel Binary Bit fromBool False = off fromBool True = on {-# INLINE fromBool #-} -- | Test if Pixel's value is 'on'. isOn :: Pixel Binary Bit -> Bool isOn (PixelBinary (Bit 0)) = False isOn _ = True {-# INLINE isOn #-} -- | Test if Pixel's value is 'off'. isOff :: Pixel Binary Bit -> Bool isOff = not . isOn {-# INLINE isOff #-} instance ColorSpace Binary Bit where type Components Binary Bit = Bit promote = PixelBinary {-# INLINE promote #-} fromComponents = PixelBinary {-# INLINE fromComponents #-} toComponents (PixelBinary b) = b {-# INLINE toComponents #-} getPxC (PixelBinary b) _ = b {-# INLINE getPxC #-} setPxC (PixelBinary _) _ b = PixelBinary b {-# INLINE setPxC #-} mapPxC f (PixelBinary b) = PixelBinary (f Binary b) {-# INLINE mapPxC #-} liftPx f (PixelBinary b) = PixelBinary (f b) {-# INLINE liftPx #-} liftPx2 f (PixelBinary b1) (PixelBinary b2) = PixelBinary (f b1 b2) {-# INLINE liftPx2 #-} foldrPx f z (PixelBinary b) = f b z {-# INLINE foldrPx #-} foldlPx2 f !z (PixelBinary b1) (PixelBinary b2) = f z b1 b2 {-# INLINE foldlPx2 #-} instance Elevator Bit where toWord8 (Bit 0) = 0 toWord8 _ = maxBound {-# INLINE toWord8 #-} toWord16 (Bit 0) = 0 toWord16 _ = maxBound {-# INLINE toWord16 #-} toWord32 (Bit 0) = 0 toWord32 _ = maxBound {-# INLINE toWord32 #-} toWord64 (Bit 0) = 0 toWord64 _ = maxBound {-# INLINE toWord64 #-} toFloat (Bit 0) = 0 toFloat _ = 1 {-# INLINE toFloat #-} toDouble (Bit 0) = 0 toDouble _ = 1 {-# INLINE toDouble #-} fromDouble 0 = Bit 0 fromDouble _ = Bit 1 {-# INLINE fromDouble #-} instance Num Bit where (Bit 0) + (Bit 0) = Bit 0 _ + _ = Bit 1 {-# INLINE (+) #-} -- 0 - 0 = 0 -- 0 - 1 = 0 -- 1 - 0 = 1 -- 1 - 1 = 0 _ - (Bit 1) = Bit 0 _ - _ = Bit 1 {-# INLINE (-) #-} _ * (Bit 0) = Bit 0 (Bit 0) * _ = Bit 0 _ * _ = Bit 1 {-# INLINE (*) #-} abs = id {-# INLINE abs #-} signum = id {-# INLINE signum #-} fromInteger 0 = Bit 0 fromInteger _ = Bit 1 {-# INLINE fromInteger #-} instance Num (Pixel Binary Bit) where (+) = liftPx2 (+) {-# INLINE (+) #-} (-) = liftPx2 (-) {-# INLINE (-) #-} (*) = liftPx2 (*) {-# INLINE (*) #-} abs = liftPx abs {-# INLINE abs #-} signum = liftPx signum {-# INLINE signum #-} fromInteger = promote . fromInteger {-# INLINE fromInteger #-} instance Storable Bit where sizeOf _ = sizeOf (undefined :: Word8) alignment _ = alignment (undefined :: Word8) peek p = do q <- return $ castPtr p b <- peek q return (Bit b) poke p (Bit b) = do q <- return $ castPtr p poke q b instance Storable (Pixel Binary Bit) where sizeOf _ = sizeOf (undefined :: Bit) alignment _ = alignment (undefined :: Bit) peek p = do q <- return $ castPtr p b <- peek q return (PixelBinary b) poke p (PixelBinary b) = do q <- return $ castPtr p poke q b