{-# LANGUAGE OverloadedStrings #-}
module Images.Flags where
import Text.Blaze.Svg11 ((!))
import Text.Blaze.Svg11 as S
import Text.Blaze.Svg11.Attributes as A
import Core.Geometry
import Core.Utils
import Images.FlagsCoA
flags :: [ (String , S.Svg) ]
flags :: [([Char], Svg)]
flags =
[ (,) [Char]
"ad" Svg
ad
, (,) [Char]
"af" Svg
af
, (,) [Char]
"al" Svg
al
, (,) [Char]
"at" Svg
at
, (,) [Char]
"ba" Svg
ba
, (,) [Char]
"be" Svg
be
, (,) [Char]
"bg" Svg
bg
, (,) [Char]
"by" Svg
blr
, (,) [Char]
"ch" Svg
ch
, (,) [Char]
"cy" Svg
cyp
, (,) [Char]
"cz" Svg
cz
, (,) [Char]
"de" Svg
de
, (,) [Char]
"dk" Svg
dk
, (,) [Char]
"ee" Svg
ee
, (,) [Char]
"es" Svg
es
, (,) [Char]
"eu" Svg
eu
, (,) [Char]
"fi" Svg
fi
, (,) [Char]
"fr" Svg
fr
, (,) [Char]
"gr" Svg
gr
, (,) [Char]
"hr" Svg
hrv
, (,) [Char]
"ie" Svg
ie
, (,) [Char]
"is" Svg
is
, (,) [Char]
"it" Svg
it
, (,) [Char]
"li" Svg
li
, (,) [Char]
"lt" Svg
lt
, (,) [Char]
"lu" Svg
lu
, (,) [Char]
"lv" Svg
lv
, (,) [Char]
"mc" Svg
mc
, (,) [Char]
"md" Svg
md
, (,) [Char]
"me" Svg
me
, (,) [Char]
"mk" Svg
mk
, (,) [Char]
"mt" Svg
mt
, (,) [Char]
"nl" Svg
nl
, (,) [Char]
"no" Svg
no
, (,) [Char]
"pl" Svg
pl
, (,) [Char]
"pt" Svg
pt
, (,) [Char]
"ro" Svg
ro
, (,) [Char]
"rs" Svg
rs
, (,) [Char]
"ru" Svg
ru
, (,) [Char]
"se" Svg
se
, (,) [Char]
"si" Svg
si
, (,) [Char]
"sk" Svg
sk
, (,) [Char]
"sm" Svg
sm
, (,) [Char]
"ua" Svg
ua
, (,) [Char]
"uk" Svg
uk
, (,) [Char]
"va" Svg
va
, (,) [Char]
"xk" Svg
xk
]
flagV3Eq :: (Float,Float) -> String -> String -> String -> Svg
flagV3Eq :: (Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagV3Eq (Float
w,Float
h) [Char]
c1 [Char]
c2 [Char]
c3 =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox (forall a. ToValue a => a -> AttributeValue
S.toValue forall a b. (a -> b) -> a -> b
$ [Char]
"0 0 " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Float
w forall a. [a] -> [a] -> [a]
++ [Char]
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Float
h)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
100forall a. Num a => a -> a -> a
*Float
w)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
100forall a. Num a => a -> a -> a
*Float
h)
forall a b. (a -> b) -> a -> b
$ do
Svg
leftStripe
Svg
centralStripe
Svg
rightStripe
where
leftStripe :: Svg
leftStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
wforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
h)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill (forall a. ToValue a => a -> AttributeValue
S.toValue [Char]
c1)
centralStripe :: Svg
centralStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
wforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
wforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
h)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill (forall a. ToValue a => a -> AttributeValue
S.toValue [Char]
c2)
rightStripe :: Svg
rightStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2forall a. Num a => a -> a -> a
*Float
wforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
wforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
h)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill (forall a. ToValue a => a -> AttributeValue
S.toValue [Char]
c3)
flagH3Eq :: (Float,Float) -> String -> String -> String -> Svg
flagH3Eq :: (Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq (Float
w,Float
h) [Char]
c1 [Char]
c2 [Char]
c3 =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox (forall a. ToValue a => a -> AttributeValue
S.toValue forall a b. (a -> b) -> a -> b
$ [Char]
"0 0 " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Float
w forall a. [a] -> [a] -> [a]
++ [Char]
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Float
h)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
100forall a. Num a => a -> a -> a
*Float
w)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
100forall a. Num a => a -> a -> a
*Float
h)
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
midStripe
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
w)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
hforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill (forall a. ToValue a => a -> AttributeValue
S.toValue [Char]
c1)
midStripe :: Svg
midStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
hforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
w)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
hforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill (forall a. ToValue a => a -> AttributeValue
S.toValue [Char]
c2)
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2forall a. Num a => a -> a -> a
*Float
hforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
w)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
hforall a. Fractional a => a -> a -> a
/Float
3)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill (forall a. ToValue a => a -> AttributeValue
S.toValue [Char]
c3)
ad :: Svg
ad :: Svg
ad =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 20 14"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"200px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"140px"
forall a b. (a -> b) -> a -> b
$ do
Svg
leftStripe
Svg
centreStripe
Svg
rightStripe
where
leftStripe :: Svg
leftStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
6.4)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
14)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#10069F"
centreStripe :: Svg
centreStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
6.4)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
7.2)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
14)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FEDD00"
rightStripe :: Svg
rightStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
13.6)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
6.4)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
14)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#D50032"
af :: Svg
af :: Svg
af =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagV3Eq
(Float
3,Float
2)
[Char]
"rgb(0,0,0)"
[Char]
"rgb(190,0,0)"
[Char]
"rgb(0,122,54)"
al :: Svg
al :: Svg
al =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 980 700"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"490px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"350px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
alCoA
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
980)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
700)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FF0000"
at :: Svg
at :: Svg
at =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
3,Float
2)
[Char]
"#C8102E"
[Char]
"#FFFFFF"
[Char]
"#C8102E"
ba :: Svg
ba :: Svg
ba =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 400 200"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"400px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg -> Svg
defs forall a b. (a -> b) -> a -> b
$
Svg
starDef
Svg
background
Svg
triangle
Svg -> Svg
S.g forall a b. (a -> b) -> a -> b
$ do
Svg
star
Svg
star forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Integer
25 Integer
25)
Svg
star forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Integer
50 Integer
50)
Svg
star forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Integer
75 Integer
75)
Svg
star forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Integer
100 Integer
100)
Svg
star forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Integer
125 Integer
125)
Svg
star forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Integer
150 Integer
150)
Svg
star forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Integer
175 Integer
175)
Svg
star forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Integer
200 Integer
200)
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
400)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
200)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#001489"
triangle :: Svg
triangle =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFCD00"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"0"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
triangleDirs
triangleDirs :: AttributeValue
triangleDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
106 Integer
0
forall a. Show a => a -> a -> Path
l Integer
306 Integer
0
forall a. Show a => a -> a -> Path
l Integer
306 Integer
200
Path
S.z
a :: Float
a = (Float
19 forall a. Num a => a -> a -> a
* (forall a. Floating a => a -> a
sqrt Float
5) forall a. Num a => a -> a -> a
- Float
38) forall a. Fractional a => a -> a -> a
/ Float
2
starDef :: Svg
starDef =
Int -> Float -> (Float, Float) -> Svg
starRegular Int
5 Float
19 (Float
68,-Float
a)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"0"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.id_ AttributeValue
"HaskellSvgIcons-baFlagStar"
star :: Svg
star =
Svg
S.use
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.xlinkHref AttributeValue
"#HaskellSvgIcons-baFlagStar"
be :: Svg
be :: Svg
be =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagV3Eq
(Float
3,Float
2.6)
[Char]
"#000000"
[Char]
"#FFE936"
[Char]
"#FF0F21"
bg :: Svg
bg :: Svg
bg =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
5,Float
3)
[Char]
"#FFFFFF"
[Char]
"#009B74"
[Char]
"#D01C1F"
blr :: Svg
blr :: Svg
blr =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 90 45"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"400px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
botStripe
Svg
whiteStripe
Svg
ruchnik
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
10)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
80)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
30)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#CF101A"
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
10)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
30)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
80)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
15)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#007D2C"
whiteStripe :: Svg
whiteStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
9)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
45)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
ruchnikMatrix :: [[Integer]]
ruchnikMatrix =
[ [Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
0,Integer
1]
, [Integer
1,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1]
, [Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0]
, [Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0]
, [Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
1,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0]
, [Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0]
, [Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0]
, [Integer
1,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1]
, [Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
0,Integer
1]
, [Integer
0,Integer
0,Integer
1,Integer
0,Integer
0,Integer
1,Integer
0,Integer
0,Integer
1,Integer
0,Integer
0,Integer
0]
, [Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0]
, [Integer
1,Integer
1,Integer
0,Integer
1,Integer
1,Integer
0,Integer
1,Integer
1,Integer
0,Integer
1,Integer
1,Integer
0]
, [Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0]
, [Integer
0,Integer
0,Integer
1,Integer
0,Integer
0,Integer
1,Integer
0,Integer
0,Integer
1,Integer
0,Integer
0,Integer
0]
, [Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
0,Integer
1]
, [Integer
1,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1]
, [Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0]
, [Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0]
, [Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0]
, [Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1]
, [Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1]
, [Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1]
, [Integer
1,Integer
0,Integer
0,Integer
1,Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1]
, [Integer
0,Integer
0,Integer
0,Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0]
, [Integer
1,Integer
0,Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0]
, [Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
1]
, [Integer
1,Integer
1,Integer
1,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
0]
, [Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
1,Integer
0,Integer
0]
, [Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
0]
, [Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
1,Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1]
, [Integer
0,Integer
0,Integer
0,Integer
0,Integer
1,Integer
1,Integer
0,Integer
1,Integer
0,Integer
0,Integer
0,Integer
1]
]
w :: Float
w = Float
10 forall a. Fractional a => a -> a -> a
/ Float
23
h :: Float
h = Float
45 forall a. Fractional a => a -> a -> a
/ Float
61
ruchnik :: Svg
ruchnik =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#CF101A"
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.strokeWidth (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
w)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
ruchnikDirs
ruchnikDirs :: AttributeValue
ruchnikDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(\Int
n -> forall {a}. (Num a, Eq a) => Float -> [a] -> Path
drawLine (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) forall a b. (a -> b) -> a -> b
$ [[Integer]]
ruchnikMatrix forall a. [a] -> Int -> a
!! Int
n)
[Int
0 .. Int
30]
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(\Int
n -> forall {a}. (Num a, Eq a) => Float -> [a] -> Path
drawLine (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) forall a b. (a -> b) -> a -> b
$ [[Integer]]
ruchnikMatrix forall a. [a] -> Int -> a
!! (Int
60 forall a. Num a => a -> a -> a
- Int
n))
[Int
31 .. Int
60]
drawLine :: Float -> [a] -> Path
drawLine Float
n [a]
binL = do
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(\Integer
k ->
if a
0 forall a. Eq a => a -> a -> Bool
== [a]
binL forall a. [a] -> Int -> a
!! (forall a. Enum a => a -> Int
fromEnum Integer
k)
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else forall a. Show a => a -> a -> Path
m ( Float
0 forall a. Num a => a -> a -> a
+ (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
k)forall a. Num a => a -> a -> a
*Float
w forall a. Num a => a -> a -> a
+ Float
wforall a. Fractional a => a -> a -> a
/Float
2) (Float
nforall a. Num a => a -> a -> a
*Float
h) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
vr Float
h
) [Integer
0 .. Integer
10]
if a
0 forall a. Eq a => a -> a -> Bool
== [a]
binL forall a. [a] -> Int -> a
!! Int
11
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else forall a. Show a => a -> a -> Path
m Float
5 (Float
nforall a. Num a => a -> a -> a
*Float
h) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
vr Float
h
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(\Int
k ->
if a
0 forall a. Eq a => a -> a -> Bool
== [a]
binL forall a. [a] -> Int -> a
!! Int
k
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else forall a. Show a => a -> a -> Path
m (Float
10 forall a. Num a => a -> a -> a
- (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k)forall a. Num a => a -> a -> a
*Float
w forall a. Num a => a -> a -> a
- Float
wforall a. Fractional a => a -> a -> a
/Float
2) (Float
nforall a. Num a => a -> a -> a
*Float
h) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
vr Float
h
) [Int
0 .. Int
10]
ch :: S.Svg
ch :: Svg
ch =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 32 32"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"200px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
cross
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
32)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
32)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FF0000"
cross :: Svg
cross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"6"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
crossDirs :: AttributeValue
crossDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
16 Integer
6
forall a. Show a => a -> a -> Path
l Integer
16 Integer
26
forall a. Show a => a -> a -> Path
m Integer
6 Integer
16
forall a. Show a => a -> a -> Path
l Integer
26 Integer
16
cyp :: S.Svg
cyp :: Svg
cyp =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 900 600"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
cyCoA
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
900)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
600)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
cz :: S.Svg
cz :: Svg
cz =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 6 4"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
leftTriangle
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"0"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
topDirs
topDirs :: AttributeValue
topDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
0 Integer
0
forall a. Show a => a -> a -> Path
l Integer
6 Integer
0
forall a. Show a => a -> a -> Path
l Integer
6 Integer
2
forall a. Show a => a -> a -> Path
l Integer
3 Integer
2
Path
S.z
leftTriangle :: Svg
leftTriangle =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"0"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#11457E"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
triangleDirs
triangleDirs :: AttributeValue
triangleDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
0 Integer
0
forall a. Show a => a -> a -> Path
l Integer
3 Integer
2
forall a. Show a => a -> a -> Path
l Integer
0 Integer
4
Path
S.z
botStripe :: Svg
botStripe =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"0"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#D7141A"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
botDirs
botDirs :: AttributeValue
botDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
0 Integer
4
forall a. Show a => a -> a -> Path
l Integer
6 Integer
4
forall a. Show a => a -> a -> Path
l Integer
6 Integer
2
forall a. Show a => a -> a -> Path
l Integer
3 Integer
2
Path
S.z
de :: Svg
de :: Svg
de =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
5,Float
3)
[Char]
"rgb(0,0,0)"
[Char]
"rgb(255,0,0)"
[Char]
"rgb(255,204,0)"
dk :: Svg
dk :: Svg
dk =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 37 28"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"370px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"280px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
cross
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
37)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
28)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#C8102E"
cross :: Svg
cross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"4"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
crossDirs :: AttributeValue
crossDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
14 Integer
0
forall a. Show a => a -> a -> Path
l Integer
14 Integer
28
forall a. Show a => a -> a -> Path
m Integer
0 Integer
14
forall a. Show a => a -> a -> Path
l Integer
37 Integer
14
ee :: Svg
ee :: Svg
ee =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
5.5, Float
3.5)
[Char]
"#0072CE"
[Char]
"#000000"
[Char]
"#FFFFFF"
es :: Svg
es :: Svg
es =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 3 2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
redBandTop
Svg
yellowBand
Svg
redBandBot
where
colRed :: AttributeValue
colRed = AttributeValue
"rgb(198,11,30)"
colYellow :: AttributeValue
colYellow = AttributeValue
"rgb(255,196,0)"
redBandTop :: Svg
redBandTop =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0.5)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
colRed
yellowBand :: Svg
yellowBand =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
colYellow
redBandBot :: Svg
redBandBot =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0.5)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
colRed
eu :: Svg
eu :: Svg
eu =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 3 2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Float -> Svg
star [Float
0..Float
11]
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#003399"
starPos :: b -> (b, b)
starPos b
k =
( b
3forall a. Fractional a => a -> a -> a
/b
2 forall a. Num a => a -> a -> a
+ (b
2forall a. Fractional a => a -> a -> a
/b
3) forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
cos (b
kforall a. Num a => a -> a -> a
*forall a. Floating a => a
piforall a. Fractional a => a -> a -> a
/b
6)
, b
1 forall a. Num a => a -> a -> a
+ (b
2forall a. Fractional a => a -> a -> a
/b
3) forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
sin (b
kforall a. Num a => a -> a -> a
*forall a. Floating a => a
piforall a. Fractional a => a -> a -> a
/b
6)
)
star :: Float -> Svg
star Float
k =
Int -> Float -> (Float, Float) -> Svg
starRegular Int
5 (Float
1forall a. Fractional a => a -> a -> a
/Float
9) (forall {b}. Floating b => b -> (b, b)
starPos Float
k)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFCC00"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.id_ AttributeValue
"HaskellSvgIcons-euFlagStar"
fi :: S.Svg
fi :: Svg
fi =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 36 22"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"360px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"220px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
cross
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
36)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
22)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
cross :: Svg
cross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#002F6C"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"6"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
crossDirs :: AttributeValue
crossDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
13 Integer
0
forall a. Show a => a -> a -> Path
l Integer
13 Integer
26
forall a. Show a => a -> a -> Path
m Integer
0 Integer
11
forall a. Show a => a -> a -> Path
l Integer
36 Integer
11
fr :: S.Svg
fr :: Svg
fr =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagV3Eq
(Float
3,Float
2)
[Char]
"rgb(0,85,164)"
[Char]
"rgb(255,255,255"
[Char]
"rgb(239,65,53)"
gr :: Svg
gr :: Svg
gr =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 27 18"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
blueLines
Svg
whiteLines
Svg
blueSquare
Svg
greekCross
where
blueLines :: Svg
blueLines =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#004C98"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
blueDirs
whiteLines :: Svg
whiteLines =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
whiteDirs
blueDirs :: AttributeValue
blueDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
0 Integer
1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
forall a. Show a => a -> a -> Path
m Integer
0 Integer
5 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
forall a. Show a => a -> a -> Path
m Integer
0 Integer
9 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
forall a. Show a => a -> a -> Path
m Integer
0 Integer
13 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
forall a. Show a => a -> a -> Path
m Integer
0 Integer
17 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
whiteDirs :: AttributeValue
whiteDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
0 Integer
3 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
forall a. Show a => a -> a -> Path
m Integer
0 Integer
7 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
forall a. Show a => a -> a -> Path
m Integer
0 Integer
11 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
forall a. Show a => a -> a -> Path
m Integer
0 Integer
15 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Show a => a -> Path
hr Integer
27
blueSquare :: Svg
blueSquare =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
10)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
10)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#004C98"
greekCross :: Svg
greekCross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
crossDirs :: AttributeValue
crossDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
5 Integer
0
forall a. Show a => a -> a -> Path
l Integer
5 Integer
10
forall a. Show a => a -> a -> Path
m Integer
0 Integer
5
forall a. Show a => a -> a -> Path
l Integer
10 Integer
5
hrv :: Svg
hrv :: Svg
hrv =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
4,Float
2)
[Char]
"#FF0000"
[Char]
"#FFFFFF"
[Char]
"#171796"
ie :: S.Svg
ie :: Svg
ie =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagV3Eq
(Float
3,Float
1.5)
[Char]
"rgb(22,155,98)"
[Char]
"rgb(255,255,255)"
[Char]
"rgb(255,136,62)"
is :: S.Svg
is :: Svg
is =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 25 18"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"250px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"180px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
whiteCross
Svg
redCross
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
25)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
18)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#02529C"
whiteCross :: Svg
whiteCross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"4"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
redCross :: Svg
redCross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#DC1E35"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
crossDirs :: AttributeValue
crossDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
0 Integer
9
forall a. Show a => a -> a -> Path
l Integer
25 Integer
9
forall a. Show a => a -> a -> Path
m Integer
9 Integer
0
forall a. Show a => a -> a -> Path
l Integer
9 Integer
18
it :: Svg
it :: Svg
it =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagV3Eq
(Float
3,Float
2)
[Char]
"rgb(0,140,69)"
[Char]
"rgb(244,249,255"
[Char]
"rgb(205,33,42)"
li :: Svg
li :: Svg
li =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 5 3"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"500px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"300px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#002780"
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#CF0921"
lt :: Svg
lt :: Svg
lt =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
5,Float
3)
[Char]
"#FFB81C"
[Char]
"#046A38"
[Char]
"#BE3A34"
lu :: S.Svg
lu :: Svg
lu =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
3,Float
2)
[Char]
"#EA141D"
[Char]
"#FFFFFF"
[Char]
"#51ADDA"
lv :: S.Svg
lv :: Svg
lv =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 20 10"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"150px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
midStripe
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
20)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#A4343A"
midStripe :: Svg
midStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
20)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
6)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
20)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#A4343A"
mc :: S.Svg
mc :: Svg
mc =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 5 4"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"500px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"400px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#CE1126"
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
md :: Svg
md :: Svg
md =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagV3Eq
(Float
3,Float
1.5)
[Char]
"#003DA5"
[Char]
"#FFD100"
[Char]
"#C8102E"
me :: Svg
me :: Svg
me =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox (forall a. ToValue a => a -> AttributeValue
S.toValue forall a b. (a -> b) -> a -> b
$ [Char]
"0 0 " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Float
w forall a. [a] -> [a] -> [a]
++ [Char]
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Float
h)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"400px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
border
where
w :: Float
w = Float
400
h :: Float
h = Float
200
s :: Float
s = Float
h forall a. Fractional a => a -> a -> a
/ Float
40
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
400)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
200)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FF0000"
border :: Svg
border =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#E6B319"
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.strokeWidth (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2forall a. Num a => a -> a -> a
*Float
s)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
borderDirs
borderDirs :: AttributeValue
borderDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m (Float
0 forall a. Num a => a -> a -> a
+ Float
s) (Float
0 forall a. Num a => a -> a -> a
+ Float
s)
forall a. Show a => a -> a -> Path
l (Float
w forall a. Num a => a -> a -> a
- Float
s) (Float
0 forall a. Num a => a -> a -> a
+ Float
s)
forall a. Show a => a -> a -> Path
l (Float
w forall a. Num a => a -> a -> a
- Float
s) (Float
h forall a. Num a => a -> a -> a
- Float
s)
forall a. Show a => a -> a -> Path
l (Float
0 forall a. Num a => a -> a -> a
+ Float
s) (Float
h forall a. Num a => a -> a -> a
- Float
s)
Path
S.z
mk :: Svg
mk :: Svg
mk =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 2 1"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"400px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
rays
Svg
sun
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#CE2028"
d :: Float
d = Float
2forall a. Fractional a => a -> a -> a
/Float
7
sun :: Svg
sun =
Svg
S.circle
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.cx (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.cy (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.r (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
dforall a. Fractional a => a -> a -> a
/Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#F9D616"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#CE2028"
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.strokeWidth (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
dforall a. Fractional a => a -> a -> a
/Float
8)
rays :: Svg
rays =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"0"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#F9D616"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
raysDirs
x1 :: Double
x1 = Double
1 forall a. Num a => a -> a -> a
+ (Double
1forall a. Fractional a => a -> a -> a
/Double
68) forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
sqrt (Double
3825 forall a. Fractional a => a -> a -> a
/ Double
98)
x2 :: Double
x2 = Double
1 forall a. Num a => a -> a -> a
- (Double
1forall a. Fractional a => a -> a -> a
/Double
68) forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
sqrt (Double
3825 forall a. Fractional a => a -> a -> a
/ Double
98)
y1 :: Double
y1 = (Double
3forall a. Fractional a => a -> a -> a
/Double
5) forall a. Num a => a -> a -> a
* Double
x1 forall a. Num a => a -> a -> a
- Double
1forall a. Fractional a => a -> a -> a
/Double
10
y2 :: Double
y2 = (Double
3forall a. Fractional a => a -> a -> a
/Double
5) forall a. Num a => a -> a -> a
* Double
x2 forall a. Num a => a -> a -> a
- Double
1forall a. Fractional a => a -> a -> a
/Double
10
raysDirs :: AttributeValue
raysDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m (Double
1 forall a. Num a => a -> a -> a
- Double
0.1) (Double
0)
forall a. Show a => a -> a -> Path
l (Double
1 forall a. Num a => a -> a -> a
+ Double
0.1) (Double
0)
forall a. Show a => a -> a -> Path
l (Float
1 ) (Float
0.5 forall a. Num a => a -> a -> a
- Float
dforall a. Fractional a => a -> a -> a
/Float
2 forall a. Num a => a -> a -> a
+ Float
dforall a. Fractional a => a -> a -> a
/Float
8)
Path
S.z
forall a. Show a => a -> a -> Path
m (Double
1 forall a. Num a => a -> a -> a
- Double
0.1) (Double
1)
forall a. Show a => a -> a -> Path
l (Double
1 forall a. Num a => a -> a -> a
+ Double
0.1) (Double
1)
forall a. Show a => a -> a -> Path
l (Float
1 ) (Float
0.5 forall a. Num a => a -> a -> a
+ Float
dforall a. Fractional a => a -> a -> a
/Float
2 forall a. Num a => a -> a -> a
- Float
dforall a. Fractional a => a -> a -> a
/Float
8)
Path
S.z
forall a. Show a => a -> a -> Path
m (Double
0 ) (Double
0.5 forall a. Num a => a -> a -> a
- Double
0.1)
forall a. Show a => a -> a -> Path
l (Double
0 ) (Double
0.5 forall a. Num a => a -> a -> a
+ Double
0.1)
forall a. Show a => a -> a -> Path
l (Double
1 ) Double
0.5
Path
S.z
forall a. Show a => a -> a -> Path
m (Double
2 ) (Double
0.5 forall a. Num a => a -> a -> a
- Double
0.1)
forall a. Show a => a -> a -> Path
l (Double
2 ) (Double
0.5 forall a. Num a => a -> a -> a
+ Double
0.1)
forall a. Show a => a -> a -> Path
l (Double
1 ) Double
0.5
Path
S.z
forall a. Show a => a -> a -> Path
m (Integer
0 ) Integer
0
forall a. Show a => a -> a -> Path
l (Double
0 forall a. Num a => a -> a -> a
+ Double
0.3) Double
0
forall a. Show a => a -> a -> Path
l Double
x1 Double
y1
Path
S.z
forall a. Show a => a -> a -> Path
m (Double
2 forall a. Num a => a -> a -> a
- Double
0.3) Double
0
forall a. Show a => a -> a -> Path
l (Integer
2 ) Integer
0
forall a. Show a => a -> a -> Path
l Double
x2 Double
y1
Path
S.z
forall a. Show a => a -> a -> Path
m (Double
2 forall a. Num a => a -> a -> a
- Double
0.3) Double
1
forall a. Show a => a -> a -> Path
l (Integer
2 ) Integer
1
forall a. Show a => a -> a -> Path
l Double
x2 Double
y2
Path
S.z
forall a. Show a => a -> a -> Path
m (Integer
0 ) Integer
1
forall a. Show a => a -> a -> Path
l (Double
0 forall a. Num a => a -> a -> a
+ Double
0.3) Double
1
forall a. Show a => a -> a -> Path
l Double
x1 Double
y2
Path
S.z
mt :: Svg
mt :: Svg
mt =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 3 2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
leftStripe
Svg
rightStripe
where
leftStripe :: Svg
leftStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
rightStripe :: Svg
rightStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#C01B22"
nl :: S.Svg
nl :: Svg
nl =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
3,Float
2)
[Char]
"#AE1C28"
[Char]
"#FFFFFF"
[Char]
"#21468B"
no :: S.Svg
no :: Svg
no =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 22 16"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"330px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"240px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
whiteCross
Svg
blueCross
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
22)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
16)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#BA0C2F"
whiteCross :: Svg
whiteCross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#FFFFFF"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"4"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
blueCross :: Svg
blueCross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#00205B"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
crossDirs :: AttributeValue
crossDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
8 Integer
0
forall a. Show a => a -> a -> Path
l Integer
8 Integer
16
forall a. Show a => a -> a -> Path
m Integer
0 Integer
8
forall a. Show a => a -> a -> Path
l Integer
22 Integer
8
pl :: Svg
pl :: Svg
pl =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 8 5"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"400px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"250px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
8)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2.5)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
8)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2.5)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#DC143C"
pt :: S.Svg
pt :: Svg
pt =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 3 2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
greenBand
Svg
redBand
where
greenBand :: Svg
greenBand =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
6forall a. Fractional a => a -> a -> a
/Float
5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"rgb(0,102,0)"
redBand :: Svg
redBand =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
6forall a. Fractional a => a -> a -> a
/Float
5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
9forall a. Fractional a => a -> a -> a
/Float
5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"rgb(255,0,0)"
ro :: Svg
ro :: Svg
ro =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagV3Eq
(Float
3,Float
2)
[Char]
"#002B7F"
[Char]
"#FCD116"
[Char]
"#CE1126"
rs :: Svg
rs :: Svg
rs =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
3,Float
2)
[Char]
"#C7363D"
[Char]
"#0C4077"
[Char]
"#FFFFFF"
ru :: S.Svg
ru :: Svg
ru =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
3,Float
2)
[Char]
"#FFFFFF"
[Char]
"#0039A6"
[Char]
"#E4181C"
se :: S.Svg
se :: Svg
se =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 16 10"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"320px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
cross
where
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
16)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
10)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#006AA7"
cross :: Svg
cross =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"#FECC02"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeWidth AttributeValue
"2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
crossDirs
crossDirs :: AttributeValue
crossDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
6 Integer
0
forall a. Show a => a -> a -> Path
l Integer
6 Integer
10
forall a. Show a => a -> a -> Path
m Integer
0 Integer
5
forall a. Show a => a -> a -> Path
l Integer
16 Integer
5
si :: Svg
si :: Svg
si =
(Float, Float) -> [Char] -> [Char] -> [Char] -> Svg
flagH3Eq
(Float
4,Float
2)
[Char]
"#FFFFFF"
[Char]
"#0000FF"
[Char]
"#FF0000"
sk :: Svg
sk :: Svg
sk =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 18 12"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"360px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"240px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
midStripe
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
18)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
midStripe :: Svg
midStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
18)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#0B4EA2"
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
8)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
18)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#EE1C25"
sm :: Svg
sm :: Svg
sm =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 4 3"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"400px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"300px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
4)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1.5)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#73E6F2"
ua :: S.Svg
ua :: Svg
ua =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 3 2"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"200px"
forall a b. (a -> b) -> a -> b
$ do
Svg
topStripe
Svg
botStripe
where
topStripe :: Svg
topStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#0057B7"
botStripe :: Svg
botStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
3)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFDD00"
uk :: S.Svg
uk :: Svg
uk =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 50 30"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"250px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"150px"
forall a b. (a -> b) -> a -> b
$ do
Svg
scotland
Svg
irelandBase
Svg
irelandBase forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> a -> AttributeValue
rotateAround Float
180 Float
mx Float
my)
Svg
englandRed
Svg
englandWhite
where
w :: Float
w = Float
50
h :: Float
h = Float
30
mx :: Float
mx = Float
w forall a. Fractional a => a -> a -> a
/ Float
2
my :: Float
my = Float
h forall a. Fractional a => a -> a -> a
/ Float
2
x1 :: Float
x1 = Float
2 forall a. Fractional a => a -> a -> a
/ forall a. Floating a => a -> a
sin (forall a. Floating a => a -> a
atan (Float
3forall a. Fractional a => a -> a -> a
/Float
5))
y1 :: Float
y1 = Float
2 forall a. Fractional a => a -> a -> a
/ forall a. Floating a => a -> a
sin (forall a. Floating a => a -> a
atan (Float
5forall a. Fractional a => a -> a -> a
/Float
3))
colWhite :: AttributeValue
colWhite = AttributeValue
"white"
colBlue :: AttributeValue
colBlue = AttributeValue
"rgb(1,33,105)"
colRed :: AttributeValue
colRed = AttributeValue
"rgb(200,16,46)"
scotland :: Svg
scotland = do
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
w)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
h)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
colBlue
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.strokeWidth (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
6)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
colWhite
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
scotlandDirs
scotlandDirs :: AttributeValue
scotlandDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
0 Integer
0
forall a. Show a => a -> a -> Path
l Float
w Float
h
forall a. Show a => a -> a -> Path
m Float
0 Float
h
forall a. Show a => a -> a -> Path
l Float
w Float
0
irelandBase :: Svg
irelandBase =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
colRed
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
irelandDirs
irelandDirs :: AttributeValue
irelandDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Integer
0 Integer
0
forall a. Show a => a -> a -> Path
l Float
0 Float
y1
forall a. Show a => a -> a -> Path
l (Float
mx forall a. Num a => a -> a -> a
- Float
x1) Float
my
forall a. Show a => a -> a -> Path
l Float
mx Float
my
Path
S.z
forall a. Show a => a -> a -> Path
m Float
0 Float
h
forall a. Show a => a -> a -> Path
l Float
x1 Float
h
forall a. Show a => a -> a -> Path
l Float
mx (Float
my forall a. Num a => a -> a -> a
+ Float
y1)
forall a. Show a => a -> a -> Path
l Float
mx Float
my
Path
S.z
englandRed :: Svg
englandRed =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.strokeWidth (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
6)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
colRed
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
englandDirsRed
englandWhite :: Svg
englandWhite =
Svg
S.path
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.strokeWidth (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
2)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
colWhite
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
englandDirsWhite
englandDirsRed :: AttributeValue
englandDirsRed = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Float
0 Float
my
forall a. Show a => a -> a -> Path
l Float
w Float
my
forall a. Show a => a -> a -> Path
m Float
mx Float
0
forall a. Show a => a -> a -> Path
l Float
mx Float
h
englandDirsWhite :: AttributeValue
englandDirsWhite = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Float
0 (Float
my forall a. Num a => a -> a -> a
+ Float
4)
forall a. Show a => a -> a -> Path
l (Float
mx forall a. Num a => a -> a -> a
- Float
4) (Float
my forall a. Num a => a -> a -> a
+ Float
4)
forall a. Show a => a -> a -> Path
l (Float
mx forall a. Num a => a -> a -> a
- Float
4) Float
h
forall a. Show a => a -> a -> Path
m (Float
mx forall a. Num a => a -> a -> a
+ Float
4) Float
h
forall a. Show a => a -> a -> Path
l (Float
mx forall a. Num a => a -> a -> a
+ Float
4) (Float
my forall a. Num a => a -> a -> a
+ Float
4)
forall a. Show a => a -> a -> Path
l Float
w (Float
my forall a. Num a => a -> a -> a
+ Float
4)
forall a. Show a => a -> a -> Path
m Float
w (Float
my forall a. Num a => a -> a -> a
- Float
4)
forall a. Show a => a -> a -> Path
l (Float
mx forall a. Num a => a -> a -> a
+ Float
4) (Float
my forall a. Num a => a -> a -> a
- Float
4)
forall a. Show a => a -> a -> Path
l (Float
mx forall a. Num a => a -> a -> a
+ Float
4) Float
0
forall a. Show a => a -> a -> Path
m (Float
mx forall a. Num a => a -> a -> a
- Float
4) Float
0
forall a. Show a => a -> a -> Path
l (Float
mx forall a. Num a => a -> a -> a
- Float
4) (Float
my forall a. Num a => a -> a -> a
- Float
4)
forall a. Show a => a -> a -> Path
l Float
0 (Float
my forall a. Num a => a -> a -> a
- Float
4)
va :: S.Svg
va :: Svg
va =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 1 1"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"300px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"300px"
forall a b. (a -> b) -> a -> b
$ do
Svg
leftStripe
Svg
rightStripe
where
leftStripe :: Svg
leftStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFE000"
rightStripe :: Svg
rightStripe =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0.5)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
1)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"
xk :: Svg
xk :: Svg
xk =
Svg -> Svg
S.svg
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.viewbox AttributeValue
"0 0 840 600"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.width AttributeValue
"420px"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.height AttributeValue
"300px"
forall a b. (a -> b) -> a -> b
$ do
Svg
background
Svg
xkCoA
(Float, Float) -> Svg
star (Float
420 forall a. Num a => a -> a -> a
- Float
d3, Float
y3)
(Float, Float) -> Svg
star (Float
420 forall a. Num a => a -> a -> a
- Float
d2, Float
y2)
(Float, Float) -> Svg
star (Float
420 forall a. Num a => a -> a -> a
- Float
d1, Float
y1)
(Float, Float) -> Svg
star (Float
420 forall a. Num a => a -> a -> a
+ Float
d1, Float
y1)
(Float, Float) -> Svg
star (Float
420 forall a. Num a => a -> a -> a
+ Float
d2, Float
y2)
(Float, Float) -> Svg
star (Float
420 forall a. Num a => a -> a -> a
+ Float
d3, Float
y3)
where
d1 :: Float
d1 = Float
42
d2 :: Float
d2 = Float
124.3
d3 :: Float
d3 = Float
203
y1 :: Float
y1 = Float
121.7
y2 :: Float
y2 = Float
136
y3 :: Float
y3 = Float
164.8
background :: Svg
background =
Svg
S.rect
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.x (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.y (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.width (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
840)
forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.height (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
600)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.stroke AttributeValue
"none"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#244AA5"
star :: (Float, Float) -> Svg
star (Float
c0,Float
c1) =
Int -> Float -> (Float, Float) -> Svg
starRegular Int
5 Float
36 (Float
c0,Float
c1)
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#FFFFFF"