module Main where

import           System.Directory
import           Text.Blaze.Svg11 ((!))
import           Text.Blaze.Svg11 as S

import Core.Geometry
import Core.Render
import Core.Style
import Core.Utils
import Icons (exampleIcons)
import Icons.Business (svgBusiness)
import Icons.Computer (svgComputer)
import Icons.Cosmos   (svgCosmos)
import Icons.Human    (svgHuman)
import Icons.Math     (svgMath)
import Icons.Office   (svgOffice)
import Icons.Religion (svgReligion)
import Icons.Textarea (svgTextarea)
import Icons.Tools    (svgTools)
import Images.CountryFlags (countryFlags)
import Images.Mosaics      (mosaicSample)






main :: IO ()
IO ()
main = FilePath -> IO ()
renderAll FilePath
"./svg"



renderAll :: FilePath -> IO ()
renderAll :: FilePath -> IO ()
renderAll FilePath
svgFolder = do
  Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
False FilePath
svgFolder
  FilePath -> IO ()
removeDirectoryRecursive       FilePath
svgFolder
  FilePath -> IO ()
createDirectory                FilePath
svgFolder
  FilePath -> IO ()
renderExamples (FilePath
svgFolder forall a. [a] -> [a] -> [a]
++ FilePath
"/examples/")
  FilePath -> IO ()
renderIcons    (FilePath
svgFolder forall a. [a] -> [a] -> [a]
++ FilePath
"/icons/")
  FilePath -> IO ()
renderImages   (FilePath
svgFolder forall a. [a] -> [a] -> [a]
++ FilePath
"/images/")
  FilePath -> Svg -> IO ()
renderTest     (FilePath
svgFolder forall a. [a] -> [a] -> [a]
++ FilePath
"/test/") (Int -> Float -> (Float, Float) -> Svg
starRegular Int
7 Float
0.9 (Float
0,Float
0))
  FilePath -> IO ()
putStrLn FilePath
"Svg files compiled correctly"



renderExamples :: FilePath -> IO ()
renderExamples :: FilePath -> IO ()
renderExamples FilePath
path = do
  FilePath -> IO ()
createDirectory FilePath
path
  FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
path [(FilePath, Svg)]
exampleIcons



renderIcons :: FilePath -> IO ()
renderIcons :: FilePath -> IO ()
renderIcons FilePath
path = 
  do
    FilePath -> IO ()
createDirectory FilePath
path
    FilePath -> IO ()
createDirectory FilePath
businessPath
    FilePath -> IO ()
createDirectory FilePath
computerPath
    FilePath -> IO ()
createDirectory FilePath
cosmosPath
    FilePath -> IO ()
createDirectory FilePath
humanPath
    FilePath -> IO ()
createDirectory FilePath
mathPath
    FilePath -> IO ()
createDirectory FilePath
officePath
    FilePath -> IO ()
createDirectory FilePath
religionPath
    FilePath -> IO ()
createDirectory FilePath
textareaPath
    FilePath -> IO ()
createDirectory FilePath
toolsPath
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
businessPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgBusiness)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
businessPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgBusiness)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
businessPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgBusiness)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
computerPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgComputer)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
computerPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgComputer)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
computerPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgComputer)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
cosmosPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgCosmos)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
cosmosPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgCosmos)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
cosmosPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgCosmos)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
humanPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgHuman)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
humanPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgHuman)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
humanPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgHuman)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
mathPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgMath)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
mathPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgMath)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
mathPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgMath)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
officePath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgOffice)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
officePath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgOffice)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
officePath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgOffice)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
religionPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgReligion)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
religionPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgReligion)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
religionPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgReligion)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
textareaPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgTextarea)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
textareaPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgTextarea)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
textareaPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgTextarea)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
toolsPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fillIcons [(FilePath, Svg)]
svgTools)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
toolsPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
fullIcons [(FilePath, Svg)]
svgTools)
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
toolsPath (forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Svg) -> (FilePath, Svg)
strkIcons [(FilePath, Svg)]
svgTools)
  where
    fillIcons :: (FilePath, Svg) -> (FilePath, Svg)
fillIcons (FilePath
a,Svg
b) = (FilePath
a forall a. [a] -> [a] -> [a]
++ FilePath
"_fill" , Svg -> Svg
stdDims forall a b. (a -> b) -> a -> b
$ Svg -> Svg
fillStyle Svg
b)
    fullIcons :: (FilePath, Svg) -> (FilePath, Svg)
fullIcons (FilePath
a,Svg
b) = (FilePath
a forall a. [a] -> [a] -> [a]
++ FilePath
"_full" , Svg -> Svg
stdDims forall a b. (a -> b) -> a -> b
$ Svg -> Svg
fullStyle Svg
b)
    strkIcons :: (FilePath, Svg) -> (FilePath, Svg)
strkIcons (FilePath
a,Svg
b) = (FilePath
a forall a. [a] -> [a] -> [a]
++ FilePath
"_strk" , Svg -> Svg
stdDims forall a b. (a -> b) -> a -> b
$ Svg -> Svg
strkStyle Svg
b)
    -- test (a,b) = (a, coreSvg def $ b >> frame (-1) (-1) 2 2)

    businessPath :: FilePath
businessPath = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"business/"
    computerPath :: FilePath
computerPath = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"computer/"
    cosmosPath :: FilePath
cosmosPath   = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"cosmos/"
    humanPath :: FilePath
humanPath    = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"human/"
    mathPath :: FilePath
mathPath     = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"math/"
    officePath :: FilePath
officePath   = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"office/"
    religionPath :: FilePath
religionPath = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"religion/"
    textareaPath :: FilePath
textareaPath = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"textarea/"
    toolsPath :: FilePath
toolsPath    = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"tools/"



renderImages :: FilePath -> IO ()
renderImages :: FilePath -> IO ()
renderImages FilePath
path = do
    FilePath -> IO ()
createDirectory FilePath
path
    FilePath -> IO ()
createDirectory FilePath
countryFlagsPath
    FilePath -> IO ()
createDirectory FilePath
mosaicsPath
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
countryFlagsPath [(FilePath, Svg)]
countryFlags
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
mosaicsPath      [(FilePath, Svg)]
mosaicSample
  where
    countryFlagsPath :: FilePath
countryFlagsPath = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"countryFlags/"
    mosaicsPath :: FilePath
mosaicsPath      = FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
"mosaics/"



renderTest :: FilePath -> Svg -> IO ()
renderTest :: FilePath -> Svg -> IO ()
renderTest FilePath
path Svg
svgTest = do
    FilePath -> IO ()
createDirectory FilePath
path
    FilePath -> [(FilePath, Svg)] -> IO ()
renderSvgFiles FilePath
path [(FilePath, Svg)]
test
  where
    test :: [(FilePath, Svg)]
test = 
      [ (,) FilePath
"test_fill" (Svg -> Svg
stdDims forall a b. (a -> b) -> a -> b
$ Svg -> Svg
fillStyle Svg
svgFramed)
      , (,) FilePath
"test_full" (Svg -> Svg
stdDims forall a b. (a -> b) -> a -> b
$ Svg -> Svg
fullStyle Svg
svgFramed)
      , (,) FilePath
"test_strk" (Svg -> Svg
stdDims forall a b. (a -> b) -> a -> b
$ Svg -> Svg
strkStyle Svg
svgFramed)
      ]
    svgFramed :: Svg
svgFramed = 
      Svg -> Svg
S.g forall a b. (a -> b) -> a -> b
$ Svg
svgTest forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Float -> Float -> Float -> Float -> Svg
frame (-Float
1) (-Float
1) Float
2 Float
2