{-# LANGUAGE OverloadedStrings #-}
module SvgIcons.Icons.Coding
( svgCoding
, haskell
) where
import Text.Blaze.Svg11 ((!))
import Text.Blaze.Svg11 as S
import Text.Blaze.Svg11.Attributes as A
import SvgIcons.Core.Geometry
import SvgIcons.Core.Utils
svgCoding :: [ (String , S.Svg) ]
svgCoding :: [(String, MarkupM ())]
svgCoding =
[ (,) String
"haskell" MarkupM ()
haskell
]
haskell :: Svg
haskell :: MarkupM ()
haskell =
MarkupM () -> MarkupM ()
S.g
forall a b. (a -> b) -> a -> b
$ do
MarkupM ()
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#453a62"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
leftDirs
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.id_ AttributeValue
"HaskellSvgIcons-haskellLogo-left"
MarkupM ()
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#5e5086"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
midDirs
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.id_ AttributeValue
"HaskellSvgIcons-haskellLogo-mid"
MarkupM ()
S.path
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"#8f4e8b"
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
rightDirs
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.id_ AttributeValue
"HaskellSvgIcons-haskellLogo-right"
where
ks :: Double
ks = Double
0.112
tx :: Double
tx = -Double
0.5 forall a. Num a => a -> a -> a
* Double
ks forall a. Num a => a -> a -> a
* Double
17
ty :: Double
ty = -Double
0.5 forall a. Num a => a -> a -> a
* Double
ks forall a. Num a => a -> a -> a
* Double
12
f :: Double -> Double
f Double
x = Double
ks forall a. Num a => a -> a -> a
* Double
x forall a. Num a => a -> a -> a
+ Double
tx
g :: Double -> Double
g Double
y = Double
ks forall a. Num a => a -> a -> a
* Double
y forall a. Num a => a -> a -> a
+ Double
ty
x1 :: Double
x1 = Double -> Double
f Double
0
x2 :: Double
x2 = Double -> Double
f Double
3
x3 :: Double
x3 = Double -> Double
f Double
4
x4 :: Double
x4 = Double -> Double
f Double
7
x5 :: Double
x5 = Double -> Double
f Double
8
x6 :: Double
x6 = Double -> Double
f Double
9.5
x7 :: Double
x7 = Double -> Double
f Double
10.33
x8 :: Double
x8 = Double -> Double
f Double
11.66
x9 :: Double
x9 = Double -> Double
f Double
12
x10 :: Double
x10 = Double -> Double
f Double
12.33
x11 :: Double
x11 = Double -> Double
f Double
13.66
x12 :: Double
x12 = Double -> Double
f Double
15
x13 :: Double
x13 = Double -> Double
f Double
17
y1 :: Double
y1 = Double -> Double
g Double
0
y2 :: Double
y2 = Double -> Double
g Double
3.5
y3 :: Double
y3 = Double -> Double
g Double
5.5
y4 :: Double
y4 = Double -> Double
g Double
6
y5 :: Double
y5 = Double -> Double
g Double
6.5
y6 :: Double
y6 = Double -> Double
g Double
8.25
y7 :: Double
y7 = Double -> Double
g Double
8.5
y8 :: Double
y8 = Double -> Double
g Double
12
leftDirs :: AttributeValue
leftDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Double
x1 Double
y1
forall a. Show a => a -> a -> Path
l Double
x2 Double
y1
forall a. Show a => a -> a -> Path
l Double
x4 Double
y4
forall a. Show a => a -> a -> Path
l Double
x2 Double
y8
forall a. Show a => a -> a -> Path
l Double
x1 Double
y8
forall a. Show a => a -> a -> Path
l Double
x3 Double
y4
Path
S.z
midDirs :: AttributeValue
midDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Double
x3 Double
y1
forall a. Show a => a -> a -> Path
l Double
x4 Double
y1
forall a. Show a => a -> a -> Path
l Double
x12 Double
y8
forall a. Show a => a -> a -> Path
l Double
x9 Double
y8
forall a. Show a => a -> a -> Path
l Double
x6 Double
y6
forall a. Show a => a -> a -> Path
l Double
x4 Double
y8
forall a. Show a => a -> a -> Path
l Double
x3 Double
y8
forall a. Show a => a -> a -> Path
l Double
x5 Double
y4
Path
S.z
rightDirs :: AttributeValue
rightDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
forall a. Show a => a -> a -> Path
m Double
x8 Double
y3
forall a. Show a => a -> a -> Path
l Double
x7 Double
y2
forall a. Show a => a -> a -> Path
l Double
x13 Double
y2
forall a. Show a => a -> a -> Path
l Double
x13 Double
y3
Path
S.z
forall a. Show a => a -> a -> Path
m Double
x11 Double
y7
forall a. Show a => a -> a -> Path
l Double
x10 Double
y5
forall a. Show a => a -> a -> Path
l Double
x13 Double
y5
forall a. Show a => a -> a -> Path
l Double
x13 Double
y7
Path
S.z