module Reanimate.Builtin.Images
( svgLogo,
haskellLogo,
githubIcon,
githubWhiteIcon,
smallEarth,
)
where
import Codec.Picture
import qualified Data.ByteString as B
import qualified Data.Text.IO as T
import Graphics.SvgTree (parseSvgFile)
import Paths_reanimate
import Reanimate.Animation
import Reanimate.Svg
import System.IO.Unsafe
embedImage :: FilePath -> IO SVG
embedImage :: FilePath -> IO SVG
embedImage FilePath
key = do
FilePath
svg_file <- FilePath -> IO FilePath
getDataFileName FilePath
key
Text
svg_data <- FilePath -> IO Text
T.readFile FilePath
svg_file
case FilePath -> Text -> Maybe Document
parseSvgFile FilePath
svg_file Text
svg_data of
Maybe Document
Nothing -> FilePath -> IO SVG
forall a. HasCallStack => FilePath -> a
error FilePath
"Malformed svg"
Just Document
svg -> SVG -> IO SVG
forall (m :: * -> *) a. Monad m => a -> m a
return (SVG -> IO SVG) -> SVG -> IO SVG
forall a b. (a -> b) -> a -> b
$ Document -> SVG
embedDocument Document
svg
loadJPG :: FilePath -> Image PixelRGBA8
loadJPG :: FilePath -> Image PixelRGBA8
loadJPG FilePath
key = IO (Image PixelRGBA8) -> Image PixelRGBA8
forall a. IO a -> a
unsafePerformIO (IO (Image PixelRGBA8) -> Image PixelRGBA8)
-> IO (Image PixelRGBA8) -> Image PixelRGBA8
forall a b. (a -> b) -> a -> b
$ do
FilePath
jpg_file <- FilePath -> IO FilePath
getDataFileName FilePath
key
ByteString
dat <- FilePath -> IO ByteString
B.readFile FilePath
jpg_file
case ByteString -> Either FilePath DynamicImage
decodeJpeg ByteString
dat of
Left FilePath
err -> FilePath -> IO (Image PixelRGBA8)
forall a. HasCallStack => FilePath -> a
error FilePath
err
Right DynamicImage
img -> Image PixelRGBA8 -> IO (Image PixelRGBA8)
forall (m :: * -> *) a. Monad m => a -> m a
return (Image PixelRGBA8 -> IO (Image PixelRGBA8))
-> Image PixelRGBA8 -> IO (Image PixelRGBA8)
forall a b. (a -> b) -> a -> b
$ DynamicImage -> Image PixelRGBA8
convertRGBA8 DynamicImage
img
svgLogo :: SVG
svgLogo :: SVG
svgLogo = IO SVG -> SVG
forall a. IO a -> a
unsafePerformIO (IO SVG -> SVG) -> IO SVG -> SVG
forall a b. (a -> b) -> a -> b
$ FilePath -> IO SVG
embedImage FilePath
"data/svg-logo.svg"
haskellLogo :: SVG
haskellLogo :: SVG
haskellLogo = IO SVG -> SVG
forall a. IO a -> a
unsafePerformIO (IO SVG -> SVG) -> IO SVG -> SVG
forall a b. (a -> b) -> a -> b
$ FilePath -> IO SVG
embedImage FilePath
"data/haskell.svg"
githubIcon :: SVG
githubIcon :: SVG
githubIcon = IO SVG -> SVG
forall a. IO a -> a
unsafePerformIO (IO SVG -> SVG) -> IO SVG -> SVG
forall a b. (a -> b) -> a -> b
$ FilePath -> IO SVG
embedImage FilePath
"data/github-icon.svg"
{-# NOINLINE githubWhiteIcon #-}
githubWhiteIcon :: SVG
githubWhiteIcon :: SVG
githubWhiteIcon = IO SVG -> SVG
forall a. IO a -> a
unsafePerformIO (IO SVG -> SVG) -> IO SVG -> SVG
forall a b. (a -> b) -> a -> b
$ FilePath -> IO SVG
embedImage FilePath
"data/github-icon-white.svg"
smallEarth :: Image PixelRGBA8
smallEarth :: Image PixelRGBA8
smallEarth = FilePath -> Image PixelRGBA8
loadJPG FilePath
"data/small_earth.jpg"