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

import           Foreign.C.Types

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

newtype DistortImageMethod = DistortImageMethod { unDistortImageMethod :: CInt }

undefinedDistortion  :: DistortImageMethod
undefinedDistortion  = DistortImageMethod 0
affineDistortion  :: DistortImageMethod
affineDistortion  = DistortImageMethod 1
affineProjectionDistortion  :: DistortImageMethod
affineProjectionDistortion  = DistortImageMethod 2
scaleRotateTranslateDistortion  :: DistortImageMethod
scaleRotateTranslateDistortion  = DistortImageMethod 3
perspectiveDistortion  :: DistortImageMethod
perspectiveDistortion  = DistortImageMethod 4
perspectiveProjectionDistortion  :: DistortImageMethod
perspectiveProjectionDistortion  = DistortImageMethod 5
bilinearForwardDistortion  :: DistortImageMethod
bilinearForwardDistortion  = DistortImageMethod 6
bilinearReverseDistortion  :: DistortImageMethod
bilinearReverseDistortion  = DistortImageMethod 7
polynomialDistortion  :: DistortImageMethod
polynomialDistortion  = DistortImageMethod 8
arcDistortion  :: DistortImageMethod
arcDistortion  = DistortImageMethod 9
polarDistortion  :: DistortImageMethod
polarDistortion  = DistortImageMethod 10
dePolarDistortion  :: DistortImageMethod
dePolarDistortion  = DistortImageMethod 11
cylinder2PlaneDistortion  :: DistortImageMethod
cylinder2PlaneDistortion  = DistortImageMethod 12
plane2CylinderDistortion  :: DistortImageMethod
plane2CylinderDistortion  = DistortImageMethod 13
barrelDistortion  :: DistortImageMethod
barrelDistortion  = DistortImageMethod 14
barrelInverseDistortion  :: DistortImageMethod
barrelInverseDistortion  = DistortImageMethod 15
shepardsDistortion  :: DistortImageMethod
shepardsDistortion  = DistortImageMethod 16
resizeDistortion  :: DistortImageMethod
resizeDistortion  = DistortImageMethod 17
sentinelDistortion  :: DistortImageMethod
sentinelDistortion  = DistortImageMethod 18

{-# LINE 32 "Graphics/ImageMagick/MagickCore/Types/FFI/Distort.hsc" #-}

bilinearDistortion = bilinearForwardDistortion

newtype SparseColorMethod = SparseColorMethod { unSparseColorMethod :: CInt }

undefinedColorInterpolate  :: SparseColorMethod
undefinedColorInterpolate  = SparseColorMethod 0
barycentricColorInterpolate  :: SparseColorMethod
barycentricColorInterpolate  = SparseColorMethod 1
bilinearColorInterpolate  :: SparseColorMethod
bilinearColorInterpolate  = SparseColorMethod 7
polynomialColorInterpolate  :: SparseColorMethod
polynomialColorInterpolate  = SparseColorMethod 8
shepardsColorInterpolate  :: SparseColorMethod
shepardsColorInterpolate  = SparseColorMethod 16
voronoiColorInterpolate  :: SparseColorMethod
voronoiColorInterpolate  = SparseColorMethod 18
inverseColorInterpolate  :: SparseColorMethod
inverseColorInterpolate  = SparseColorMethod 19

{-# LINE 46 "Graphics/ImageMagick/MagickCore/Types/FFI/Distort.hsc" #-}