{-# LANGUAGE     OverloadedStrings       #-}



module SvgIcons.Icons.Human 
  ( svgHuman
  , carnet
  , eyeOpened
  , eyeStriked
  , heartFat
  , heartSlim
  , people
  , person
  , talk
  ) where

import           Text.Blaze.Svg11 ((!))
import           Text.Blaze.Svg11 as S
import           Text.Blaze.Svg11.Attributes as A

import SvgIcons.Core.Utils


{- |
A list with all the icons of this module, 
together with appropriate names.

>svgHuman :: [ (String , S.Svg) ]
>svgHuman =
>  [ (,) "carnet"      carnet
>  , (,) "eyeOpened"   eyeOpened
>  , (,) "eyeStriked"  eyeStriked
>  , (,) "heartFat"    heartFat
>  , (,) "heartSlim"   heartSlim
>  , (,) "people"      people
>  , (,) "person"      person
>  , (,) "talk"        talk
>  ]
-}
svgHuman :: [ (String , S.Svg) ]
svgHuman :: [(String, MarkupM ())]
svgHuman =
  [ (,) String
"carnet"      MarkupM ()
carnet
  , (,) String
"eyeOpened"   MarkupM ()
eyeOpened
  , (,) String
"eyeStriked"  MarkupM ()
eyeStriked
  , (,) String
"heartFat"    MarkupM ()
heartFat
  , (,) String
"heartSlim"   MarkupM ()
heartSlim
  , (,) String
"people"      MarkupM ()
people
  , (,) String
"person"      MarkupM ()
person
  , (,) String
"talk"        MarkupM ()
talk
  ]


--------------------------------------------------------------------------------




{- |
![fill style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/eyeOpened_fill.svg)

![fill and stroke](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/eyeOpened_full.svg)

![stroke style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/eyeOpened_strk.svg)
-}
eyeOpened :: S.Svg
eyeOpened :: MarkupM ()
eyeOpened =
  MarkupM () -> MarkupM ()
S.g forall a b. (a -> b) -> a -> b
$ do
    MarkupM ()
eye
    MarkupM ()
pupil
    MarkupM ()
glow
  where
    w :: Double
w  = Double
0.9
    c1 :: Float
c1 = Float
0
    c2 :: Float
c2 = -Float
0.2
    cr :: Float
cr = Float
0.46
    k :: Float
k  = Float
0.25
    eye :: MarkupM ()
eye = 
      MarkupM ()
S.path
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
eyePath
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeLinejoin AttributeValue
"round"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fill AttributeValue
"white"
    eyePath :: AttributeValue
eyePath = Path -> AttributeValue
S.mkPath forall a b. (a -> b) -> a -> b
$ do
      forall a. Show a => a -> a -> Path
m   (-Double
w)   Double
0
      forall a. Show a => a -> a -> a -> a -> a -> a -> Path
c   (-Double
0.5) (-Double
0.9) ( Double
0.5) (-Double
0.9) ( Double
w) Double
0
      forall a. Show a => a -> a -> a -> a -> a -> a -> Path
c   ( Double
0.5) ( Double
0.9) (-Double
0.5) ( Double
0.9) (-Double
w) Double
0
      Path
S.z
    pupil :: MarkupM ()
pupil =
      MarkupM ()
S.circle
        forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.cx (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
c1)
        forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.cy (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
c2)
        forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.r  (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
cr)
    glow :: MarkupM ()
glow =
      MarkupM ()
S.path
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
glowPath
        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
"white"
        forall h. Attributable h => h -> Attribute -> h
! (AttributeValue -> Attribute
A.strokeWidth (AttributeValue -> Attribute) -> Float -> Attribute
.: Float
0.5 forall a. Num a => a -> a -> a
* Float
k)
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeLinecap AttributeValue
"round"
    glowPath :: AttributeValue
glowPath = Path -> AttributeValue
S.mkPath forall a b. (a -> b) -> a -> b
$ do
      forall a. Show a => a -> a -> Path
m   (Float
c1 forall a. Num a => a -> a -> a
- Float
k)   Float
c2
      forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa  Float
k  Float
k  Float
0  Bool
False  Bool
True  Float
c1  (Float
c2 forall a. Num a => a -> a -> a
- Float
k)



{- |
![fill style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/eyeStriked_fill.svg)

![fill and stroke](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/eyeStriked_full.svg)

![stroke style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/eyeStriked_strk.svg)
-}
eyeStriked :: S.Svg
eyeStriked :: MarkupM ()
eyeStriked =
  MarkupM () -> MarkupM ()
S.g forall a b. (a -> b) -> a -> b
$ do
    MarkupM ()
eyeOpened
    MarkupM ()
bar
  where
    k :: Double
k = Double
0.9
    bar :: MarkupM ()
bar =
      MarkupM ()
S.path
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
barPath
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeLinecap AttributeValue
"round"
    barPath :: AttributeValue
barPath = Path -> AttributeValue
S.mkPath forall a b. (a -> b) -> a -> b
$ do
      forall a. Show a => a -> a -> Path
m  ( Double
k) (-Double
k)
      forall a. Show a => a -> a -> Path
l  (-Double
k) ( Double
k)



{- |
![fill style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/person_fill.svg)

![fill and stroke](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/person_full.svg)

![stroke style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/person_strk.svg)
-}
person :: S.Svg
person :: MarkupM ()
person =
  MarkupM () -> MarkupM ()
S.g forall a b. (a -> b) -> a -> b
$ do
    MarkupM ()
simpleShoulders
    MarkupM ()
simpleHead
  where
    kx :: Double
kx =  Double
0.7
    ky :: Double
ky =  Double
0.52
    kr :: Double
kr = (Double
1 forall a. Num a => a -> a -> a
- Double
kx)
    simpleHead :: MarkupM ()
simpleHead =
      MarkupM ()
circle
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
cx AttributeValue
"0"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
cy AttributeValue
"-0.5"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
r  AttributeValue
"0.35"
    simpleShoulders :: MarkupM ()
simpleShoulders =
      MarkupM ()
S.path
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
d AttributeValue
shouldersPath
    shouldersPath :: AttributeValue
shouldersPath =
      Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
        forall a. Show a => a -> a -> Path
m  Double
kx  Double
ky
        forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa Double
kr  Double
kr   Double
0 Bool
True Bool
False (-Double
kx) Double
ky
        forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa Double
kr  Double
0.15 Double
0 Bool
True Bool
False   Double
kx  Double
ky



{- |
![fill style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/people_fill.svg)

![fill and stroke](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/people_full.svg)

![stroke style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/people_strk.svg)
-}
people :: S.Svg
people :: MarkupM ()
people =
  MarkupM () -> MarkupM ()
S.g forall a b. (a -> b) -> a -> b
$ do
    MarkupM ()
person forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate   Double
0.4  (-Double
0.2) forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> a -> AttributeValue
S.scale Double
0.8 Double
0.8)
    MarkupM ()
person forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate (-Double
0.4) (-Double
0.2) forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> a -> AttributeValue
S.scale Double
0.8 Double
0.8)
    MarkupM ()
person forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate   Double
0    ( Double
0.2) forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> a -> AttributeValue
S.scale Double
0.9 Double
0.9)



{- |
![fill style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/carnet_fill.svg)

![fill and stroke](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/carnet_full.svg)

![stroke style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/carnet_strk.svg)
-}
carnet :: S.Svg
carnet :: MarkupM ()
carnet =
  MarkupM () -> MarkupM ()
S.g forall a b. (a -> b) -> a -> b
$ do
    MarkupM ()
cardBorder
    MarkupM ()
textLines forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate ( Double
0.4) Double
0 forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> a -> AttributeValue
S.scale Double
0.5 Double
0.5)
    MarkupM ()
person    forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate (-Double
0.5) Double
0 forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> a -> AttributeValue
S.scale Double
0.5 Double
0.5)
  where
    w1 :: Double
w1 = Double
0.01
    x1 :: Double
x1 = Double
1.618 forall a. Num a => a -> a -> a
* Double
y1
    y1 :: Double
y1 = Double
0.58
    cardBorder :: MarkupM ()
cardBorder =
      MarkupM ()
S.path
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
d AttributeValue
cardBorderPath
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
fillRule AttributeValue
"evenodd"
    cardBorderPath :: AttributeValue
cardBorderPath =
      Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
        forall a. Show a => a -> a -> Path
m   (-Double
x1 forall a. Num a => a -> a -> a
- Double
w1)  (-Double
y1 forall a. Num a => a -> a -> a
- Double
w1)
        forall a. Show a => a -> a -> Path
l   ( Double
x1 forall a. Num a => a -> a -> a
+ Double
w1)  (-Double
y1 forall a. Num a => a -> a -> a
- Double
w1)
        forall a. Show a => a -> a -> Path
l   ( Double
x1 forall a. Num a => a -> a -> a
+ Double
w1)  ( Double
y1 forall a. Num a => a -> a -> a
+ Double
w1)
        forall a. Show a => a -> a -> Path
l   (-Double
x1 forall a. Num a => a -> a -> a
- Double
w1)  ( Double
y1 forall a. Num a => a -> a -> a
+ Double
w1)
        Path
S.z
        forall a. Show a => a -> a -> Path
m   (-Double
x1 forall a. Num a => a -> a -> a
+ Double
w1)  (-Double
y1 forall a. Num a => a -> a -> a
+ Double
w1)
        forall a. Show a => a -> a -> Path
l   ( Double
x1 forall a. Num a => a -> a -> a
- Double
w1)  (-Double
y1 forall a. Num a => a -> a -> a
+ Double
w1)
        forall a. Show a => a -> a -> Path
l   ( Double
x1 forall a. Num a => a -> a -> a
- Double
w1)  ( Double
y1 forall a. Num a => a -> a -> a
- Double
w1)
        forall a. Show a => a -> a -> Path
l   (-Double
x1 forall a. Num a => a -> a -> a
+ Double
w1)  ( Double
y1 forall a. Num a => a -> a -> a
- Double
w1)
        Path
S.z
    w2 :: Double
w2 =  Double
0.06
    h1 :: Double
h1 = -Double
0.5
    h2 :: Double
h2 =  Double
0
    h3 :: Double
h3 =  Double
0.5
    k1 :: Double
k1 = -Double
0.7
    k2 :: Double
k2 =  Double
0.7
    textLines :: MarkupM ()
textLines =
      MarkupM ()
S.path
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
d (Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ Double -> Path
line Double
h1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Double -> Path
line Double
h2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Double -> Path
line Double
h3)
    line :: Double -> Path
line Double
hy = do
      forall a. Show a => a -> a -> Path
m   Double
k1  (Double
hy forall a. Num a => a -> a -> a
- Double
w2)
      forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa  Double
w2  Double
w2  Double
0  Bool
True  Bool
False Double
k1 (Double
hy forall a. Num a => a -> a -> a
+ Double
w2)
      forall a. Show a => a -> a -> Path
l   Double
k2  (Double
hy forall a. Num a => a -> a -> a
+ Double
w2)
      forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa  Double
w2  Double
w2  Double
0  Bool
True  Bool
False Double
k2 (Double
hy forall a. Num a => a -> a -> a
- Double
w2)
      Path
S.z



{- |
![fill style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/heartFat_fill.svg)

![fill and stroke](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/heartFat_full.svg)

![stroke style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/heartFat_strk.svg)
-}
heartFat :: Svg
heartFat :: MarkupM ()
heartFat =
    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.d AttributeValue
heartDirs
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeLinejoin AttributeValue
"round"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.transform (forall a. Show a => a -> a -> AttributeValue
translate Double
0 Double
0.1 forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> a -> AttributeValue
S.scale Double
1.2 Double
1.2)
  where
    h :: Float
h = Float
0.06
    (Float
h1x , Float
h1y) = ( Float
0       , -Float
0.6      )
    (Float
h2x , Float
h2y) = ( Float
h1x forall a. Num a => a -> a -> a
- Float
h ,  Float
h1y forall a. Num a => a -> a -> a
- Float
h  )
    (Float
h3x , Float
h3y) = ( Float
h2y     ,  Float
h2x      )
    (Float
h4x , Float
h4y) = ( Float
0       ,  Float
0.6     )
    (Float
hqx , Float
hqy) = (-Float
0.1     ,  Float
0.6      )
    rh :: Float
rh = Float
0.5 forall a. Num a => a -> a -> a
* (Float, Float) -> (Float, Float) -> Float
distance (Float
h2x,Float
h2y) (Float
h3x,Float
h3y)
    heartDirs :: AttributeValue
heartDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
      forall a. Show a => a -> a -> Path
m   Float
h1x Float
h1y
      forall a. Show a => a -> a -> Path
l   Float
h2x Float
h2y
      forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa  Float
rh  Float
rh  Float
0  Bool
False Bool
False  Float
h3x  Float
h3y
      forall a. Show a => a -> a -> a -> a -> Path
q   Float
hqx Float
hqy Float
h4x Float
h4y
      forall a. Show a => a -> a -> a -> a -> Path
q   (-Float
hqx) ( Float
hqy) (-Float
h3x) ( Float
h3y)
      forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa  Float
rh  Float
rh  Float
0  Bool
False Bool
False (-Float
h2x) Float
h2y
      Path
S.z



{- |
![fill style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/heartSlim_fill.svg)

![fill and stroke](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/heartSlim_full.svg)

![stroke style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/heartSlim_strk.svg)
-}
heartSlim :: Svg
heartSlim :: MarkupM ()
heartSlim =
    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.d AttributeValue
heartDirs
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeLinejoin AttributeValue
"round"
  where
    h :: Float
h = Float
0.2
    (Float
h1x , Float
h1y) = ( Float
0       , -Float
0.6      )
    (Float
h2x , Float
h2y) = ( Float
h1x forall a. Num a => a -> a -> a
- Float
h ,  Float
h1y forall a. Num a => a -> a -> a
- Float
h  )
    (Float
h3x , Float
h3y) = ( Float
h2y     ,  Float
h2x      )
    (Float
h4x , Float
h4y) = ( Float
0       ,  Float
0.9      )
    (Float
hqx , Float
hqy) = (-Float
0.1     ,  Float
0.4      )
    rh :: Float
rh = Float
0.5 forall a. Num a => a -> a -> a
* (Float, Float) -> (Float, Float) -> Float
distance (Float
h2x,Float
h2y) (Float
h3x,Float
h3y)
    heartDirs :: AttributeValue
heartDirs = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
      forall a. Show a => a -> a -> Path
m   Float
h1x Float
h1y
      forall a. Show a => a -> a -> Path
l   Float
h2x Float
h2y
      forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa  Float
rh  Float
rh  Float
0  Bool
False Bool
False  Float
h3x  Float
h3y
      forall a. Show a => a -> a -> a -> a -> Path
q   Float
hqx Float
hqy Float
h4x Float
h4y
      forall a. Show a => a -> a -> a -> a -> Path
q   (-Float
hqx) ( Float
hqy) (-Float
h3x) ( Float
h3y)
      forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa  Float
rh  Float
rh  Float
0  Bool
False Bool
False (-Float
h2x) Float
h2y
      Path
S.z



{- |
![fill style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/talk_fill.svg)

![fill and stroke](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/talk_full.svg)

![stroke style](https://raw.githubusercontent.com/RamiroPastor/SvgIcons/main/svg/icons/human/talk_strk.svg)
-}
talk :: Svg
talk :: MarkupM ()
talk = 
    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
"none"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.d AttributeValue
bubble
      MarkupM ()
abc
  where
    bubble :: AttributeValue
bubble = Path -> AttributeValue
mkPath forall a b. (a -> b) -> a -> b
$ do
      forall a. Show a => a -> a -> Path
m   (-Double
0.56) ( Double
0.62)
      forall a. Show a => a -> a -> a -> Bool -> Bool -> a -> a -> Path
aa    Double
0.94    Double
0.78  Double
0  Bool
True  Bool
True   Double
0  (Double
0.78)
      forall a. Show a => a -> a -> Path
l   (-Double
0.60) ( Double
0.9)
      Path
S.z
    abc :: MarkupM ()
abc =
      MarkupM () -> MarkupM ()
S.text_ MarkupM ()
"ABC"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.x          AttributeValue
"0"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.y          AttributeValue
"0.18"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.textAnchor AttributeValue
"middle"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fontFamily AttributeValue
"Verdana"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fontSize   AttributeValue
"0.57"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.fontWeight AttributeValue
"bold"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.letterSpacing AttributeValue
"0.05"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeLinejoin AttributeValue
"round"
        forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.strokeLinecap  AttributeValue
"round"