module Hakyll.Images.Resize
( Width,
Height,
resize,
resizeImageCompiler,
scale,
scaleImageCompiler,
ensureFit,
ensureFitCompiler,
)
where
import Codec.Picture (convertRGBA8, decodeImage)
import Codec.Picture.Extra (scaleBilinear)
import Codec.Picture.Types (DynamicImage (..), imageHeight, imageWidth)
import Data.ByteString (ByteString)
import Data.Ratio ((%))
import Hakyll.Core.Compiler (Compiler)
import Hakyll.Core.Item (Item (..))
import Hakyll.Images.Common (Image (..), encode)
type Width = Int
type Height = Int
decodeImage' :: ByteString -> DynamicImage
decodeImage' :: ByteString -> DynamicImage
decodeImage' ByteString
im = case ByteString -> Either String DynamicImage
decodeImage ByteString
im of
Left String
msg -> String -> DynamicImage
forall a. HasCallStack => String -> a
error String
msg
Right DynamicImage
im' -> DynamicImage
im'
resize :: Width -> Height -> DynamicImage -> DynamicImage
resize :: Width -> Width -> DynamicImage -> DynamicImage
resize Width
w Width
h = 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 -> DynamicImage -> DynamicImage
scale :: Width -> Width -> DynamicImage -> DynamicImage
scale Width
w Width
h = Width -> Width -> Bool -> DynamicImage -> DynamicImage
scale' Width
w Width
h Bool
True
scale' ::
Width ->
Height ->
Bool ->
DynamicImage ->
DynamicImage
scale' :: Width -> Width -> Bool -> DynamicImage -> DynamicImage
scale' Width
w Width
h Bool
upAllowed DynamicImage
img = Width -> Width -> DynamicImage -> DynamicImage
resize Width
maxWidth Width
maxHeight DynamicImage
img
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 (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 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 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 -> DynamicImage -> DynamicImage
ensureFit :: Width -> Width -> DynamicImage -> DynamicImage
ensureFit Width
w Width
h = Width -> Width -> Bool -> DynamicImage -> DynamicImage
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
item =
let fmt :: ImageFormat
fmt = (Image -> ImageFormat
format (Image -> ImageFormat)
-> (Item Image -> Image) -> Item Image -> ImageFormat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item Image -> Image
forall a. Item a -> a
itemBody) Item Image
item
in Item Image -> Compiler (Item Image)
forall (m :: * -> *) a. Monad m => a -> m a
return (Item Image -> Compiler (Item Image))
-> Item Image -> Compiler (Item Image)
forall a b. (a -> b) -> a -> b
$ (ImageFormat -> DynamicImage -> Image
encode ImageFormat
fmt (DynamicImage -> Image)
-> (Image -> DynamicImage) -> Image -> Image
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Width -> Width -> DynamicImage -> DynamicImage
resize Width
w Width
h (DynamicImage -> DynamicImage)
-> (Image -> DynamicImage) -> Image -> DynamicImage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> DynamicImage
decodeImage' (ByteString -> DynamicImage)
-> (Image -> ByteString) -> Image -> DynamicImage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image -> ByteString
image) (Image -> Image) -> Item Image -> Item Image
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Item Image
item
scaleImageCompiler :: Width -> Height -> Item Image -> Compiler (Item Image)
scaleImageCompiler :: Width -> Width -> Item Image -> Compiler (Item Image)
scaleImageCompiler Width
w Width
h Item Image
item =
let fmt :: ImageFormat
fmt = (Image -> ImageFormat
format (Image -> ImageFormat)
-> (Item Image -> Image) -> Item Image -> ImageFormat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item Image -> Image
forall a. Item a -> a
itemBody) Item Image
item
in Item Image -> Compiler (Item Image)
forall (m :: * -> *) a. Monad m => a -> m a
return (Item Image -> Compiler (Item Image))
-> Item Image -> Compiler (Item Image)
forall a b. (a -> b) -> a -> b
$ (ImageFormat -> DynamicImage -> Image
encode ImageFormat
fmt (DynamicImage -> Image)
-> (Image -> DynamicImage) -> Image -> Image
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Width -> Width -> DynamicImage -> DynamicImage
scale Width
w Width
h (DynamicImage -> DynamicImage)
-> (Image -> DynamicImage) -> Image -> DynamicImage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> DynamicImage
decodeImage' (ByteString -> DynamicImage)
-> (Image -> ByteString) -> Image -> DynamicImage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image -> ByteString
image) (Image -> Image) -> Item Image -> Item Image
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Item Image
item
ensureFitCompiler :: Width -> Height -> Item Image -> Compiler (Item Image)
ensureFitCompiler :: Width -> Width -> Item Image -> Compiler (Item Image)
ensureFitCompiler Width
w Width
h Item Image
item =
let fmt :: ImageFormat
fmt = (Image -> ImageFormat
format (Image -> ImageFormat)
-> (Item Image -> Image) -> Item Image -> ImageFormat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item Image -> Image
forall a. Item a -> a
itemBody) Item Image
item
in Item Image -> Compiler (Item Image)
forall (m :: * -> *) a. Monad m => a -> m a
return (Item Image -> Compiler (Item Image))
-> Item Image -> Compiler (Item Image)
forall a b. (a -> b) -> a -> b
$ (ImageFormat -> DynamicImage -> Image
encode ImageFormat
fmt (DynamicImage -> Image)
-> (Image -> DynamicImage) -> Image -> Image
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Width -> Width -> DynamicImage -> DynamicImage
ensureFit Width
w Width
h (DynamicImage -> DynamicImage)
-> (Image -> DynamicImage) -> Image -> DynamicImage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> DynamicImage
decodeImage' (ByteString -> DynamicImage)
-> (Image -> ByteString) -> Image -> DynamicImage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image -> ByteString
image) (Image -> Image) -> Item Image -> Item Image
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Item Image
item