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

import           Foreign.C.Types

{-# LINE 8 "src/Graphics/ImageMagick/MagickCore/Types/FFI/PaintMethod.hsc" #-}

newtype PaintMethod =  PaintMethod { unPaintMethod :: CInt }


undefinedMethod  :: PaintMethod
undefinedMethod  = PaintMethod 0
pointMethod  :: PaintMethod
pointMethod  = PaintMethod 1
replaceMethod  :: PaintMethod
replaceMethod  = PaintMethod 2
floodfillMethod  :: PaintMethod
floodfillMethod  = PaintMethod 3
fillToBorderMethod  :: PaintMethod
fillToBorderMethod  = PaintMethod 4
resetMethod  :: PaintMethod
resetMethod  = PaintMethod 5

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