{-# LINE 1 "src/Graphics/ImageMagick/MagickCore/Types/FFI/DitherMethod.hsc" #-}
{-# LANGUAGE CPP                      #-}
{-# LINE 2 "src/Graphics/ImageMagick/MagickCore/Types/FFI/DitherMethod.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Graphics.ImageMagick.MagickCore.Types.FFI.DitherMethod
    where

import           Foreign.C.Types
import           Foreign.Storable

{-# LINE 10 "src/Graphics/ImageMagick/MagickCore/Types/FFI/DitherMethod.hsc" #-}

newtype DitherMethod = DitherMethod { unDitherMethod :: CInt }
    deriving (Eq,Show,Storable)

undefinedDitherFilter       :: DitherMethod
undefinedDitherFilter       = DitherMethod 0
noDitherMethod              :: DitherMethod
noDitherMethod              = DitherMethod 1
riemersmaDitherMethod       :: DitherMethod
riemersmaDitherMethod       = DitherMethod 2
floydSteinbergDitherMethod  :: DitherMethod
floydSteinbergDitherMethod  = DitherMethod 3

{-# LINE 20 "src/Graphics/ImageMagick/MagickCore/Types/FFI/DitherMethod.hsc" #-}