module Hakyll.Images.Resize
( Width,
Height,
resize,
resizeImageCompiler,
scale,
scaleImageCompiler,
ensureFit,
ensureFitCompiler,
)
where
import Codec.Picture (convertRGBA8)
import Codec.Picture.Extra (scaleBilinear)
import Codec.Picture.Types (DynamicImage (..), imageHeight, imageWidth)
import Data.Ratio ((%))
import Hakyll.Core.Compiler (Compiler)
import Hakyll.Core.Item (Item (..))
import Hakyll.Images.Common (Image (..), ImageContent, WithMetadata (..), encode, withImageContent)
type Width = Int
type Height = Int
resize :: Width -> Height -> ImageContent -> ImageContent
resize :: Width -> Width -> ImageContent -> ImageContent
resize Width
w Width
h = (DynamicImage -> DynamicImage) -> ImageContent -> ImageContent
forall a b. (a -> b) -> WithMetadata a -> WithMetadata b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Image PixelRGBA8 -> DynamicImage
ImageRGBA8 (Image PixelRGBA8 -> DynamicImage)
-> (DynamicImage -> Image PixelRGBA8)
-> DynamicImage
-> DynamicImage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Width -> Width -> Image PixelRGBA8 -> Image PixelRGBA8
forall a.
(Pixel a, Bounded (PixelBaseComponent a),
Integral (PixelBaseComponent a)) =>
Width -> Width -> Image a -> Image a
scaleBilinear Width
w Width
h (Image PixelRGBA8 -> Image PixelRGBA8)
-> (DynamicImage -> Image PixelRGBA8)
-> DynamicImage
-> Image PixelRGBA8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DynamicImage -> Image PixelRGBA8
convertRGBA8)
scale :: Width -> Height -> ImageContent -> ImageContent
scale :: Width -> Width -> ImageContent -> ImageContent
scale Width
w Width
h = Width -> Width -> Bool -> ImageContent -> ImageContent
scale' Width
w Width
h Bool
True
scale' ::
Width ->
Height ->
Bool ->
ImageContent ->
ImageContent
scale' :: Width -> Width -> Bool -> ImageContent -> ImageContent
scale' Width
w Width
h Bool
upAllowed content :: ImageContent
content@(MkWithMetadata DynamicImage
img Metadatas
_) = Width -> Width -> ImageContent -> ImageContent
resize Width
maxWidth Width
maxHeight ImageContent
content
where
img' :: Image PixelRGBA8
img' = DynamicImage -> Image PixelRGBA8
convertRGBA8 DynamicImage
img
(Width
imgWidth, Width
imgHeight) = (Image PixelRGBA8 -> Width
forall a. Image a -> Width
imageWidth Image PixelRGBA8
img', Image PixelRGBA8 -> Width
forall a. Image a -> Width
imageHeight Image PixelRGBA8
img')
resizing :: Ratio Width
resizing =
if Bool
upAllowed
then Ratio Width -> Ratio Width -> Ratio Width
forall a. Ord a => a -> a -> a
min (Width
w Width -> Width -> Ratio Width
forall a. Integral a => a -> a -> Ratio a
% Width
imgWidth) (Width
h Width -> Width -> Ratio Width
forall a. Integral a => a -> a -> Ratio a
% Width
imgHeight)
else [Ratio Width] -> Ratio Width
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [Width
w Width -> Width -> Ratio Width
forall a. Integral a => a -> a -> Ratio a
% Width
imgWidth, Width
h Width -> Width -> Ratio Width
forall a. Integral a => a -> a -> Ratio a
% Width
imgHeight, Ratio Width
1]
maxWidth :: Width
maxWidth = Ratio Width -> Width
forall b. Integral b => Ratio Width -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Ratio Width
resizing Ratio Width -> Ratio Width -> Ratio Width
forall a. Num a => a -> a -> a
* Width -> Ratio Width
forall a b. (Integral a, Num b) => a -> b
fromIntegral Width
imgWidth)
maxHeight :: Width
maxHeight = Ratio Width -> Width
forall b. Integral b => Ratio Width -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Ratio Width
resizing Ratio Width -> Ratio Width -> Ratio Width
forall a. Num a => a -> a -> a
* Width -> Ratio Width
forall a b. (Integral a, Num b) => a -> b
fromIntegral Width
imgHeight)
ensureFit :: Width -> Height -> ImageContent -> ImageContent
ensureFit :: Width -> Width -> ImageContent -> ImageContent
ensureFit Width
w Width
h = Width -> Width -> Bool -> ImageContent -> ImageContent
scale' Width
w Width
h Bool
False
resizeImageCompiler :: Width -> Height -> Item Image -> Compiler (Item Image)
resizeImageCompiler :: Width -> Width -> Item Image -> Compiler (Item Image)
resizeImageCompiler Width
w Width
h = Item Image -> Compiler (Item Image)
forall a. a -> Compiler a
forall (m :: * -> *) a. Monad m => a -> m a
return (Item Image -> Compiler (Item Image))
-> (Item Image -> Item Image)
-> Item Image
-> Compiler (Item Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Image -> Image) -> Item Image -> Item Image
forall a b. (a -> b) -> Item a -> Item b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ImageContent -> ImageContent)
-> (ImageFormat -> ImageContent -> Image) -> Image -> Image
withImageContent (Width -> Width -> ImageContent -> ImageContent
resize Width
w Width
h) ImageFormat -> ImageContent -> Image
encode)
scaleImageCompiler :: Width -> Height -> Item Image -> Compiler (Item Image)
scaleImageCompiler :: Width -> Width -> Item Image -> Compiler (Item Image)
scaleImageCompiler Width
w Width
h = Item Image -> Compiler (Item Image)
forall a. a -> Compiler a
forall (m :: * -> *) a. Monad m => a -> m a
return (Item Image -> Compiler (Item Image))
-> (Item Image -> Item Image)
-> Item Image
-> Compiler (Item Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Image -> Image) -> Item Image -> Item Image
forall a b. (a -> b) -> Item a -> Item b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ImageContent -> ImageContent)
-> (ImageFormat -> ImageContent -> Image) -> Image -> Image
withImageContent (Width -> Width -> ImageContent -> ImageContent
scale Width
w Width
h) ImageFormat -> ImageContent -> Image
encode)
ensureFitCompiler :: Width -> Height -> Item Image -> Compiler (Item Image)
ensureFitCompiler :: Width -> Width -> Item Image -> Compiler (Item Image)
ensureFitCompiler Width
w Width
h = Item Image -> Compiler (Item Image)
forall a. a -> Compiler a
forall (m :: * -> *) a. Monad m => a -> m a
return (Item Image -> Compiler (Item Image))
-> (Item Image -> Item Image)
-> Item Image
-> Compiler (Item Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Image -> Image) -> Item Image -> Item Image
forall a b. (a -> b) -> Item a -> Item b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ImageContent -> ImageContent)
-> (ImageFormat -> ImageContent -> Image) -> Image -> Image
withImageContent (Width -> Width -> ImageContent -> ImageContent
ensureFit Width
w Width
h) ImageFormat -> ImageContent -> Image
encode)