Suggestion for Gallery: Imperial Seal of Japan

34 views
Skip to first unread message

timo....@googlemail.com

unread,
May 22, 2019, 6:27:29 PM5/22/19
to diagrams-discuss
I would like to suggest as an addition to the gallery the Imperial Seal of Japan in 2 common versions: gold on white and gold on red.

It is very beautiful and easy to grasp, yet not trivial to reproduce.
The code introduces the combination of shapes to the gallery.

There is some trigonometry involved because I don't know how to construct certain points.

Should the seal be deemed not neutral enough for the gallery I provide two neutral alternatives with similar technique, a flower and an orange slice.
(But I prefer the seal for both clearer code and a more pleasing picture.)

I provide commentary as all examples in the gallery have it, but I am very appreciative of improvements in code as well as description.


> import Diagrams.Backend.SVG.CmdLine
>
> {-# LANGUAGE NoMonomorphismRestriction #-}
> {-# LANGUAGE FlexibleContexts          #-}
> {-# LANGUAGE TypeFamilies              #-}
> import Diagrams.Prelude
> import Diagrams.TwoD.Offset
> import qualified Diagrams.TwoD.Path.Boolean as B
>
>

We start with an upright petal defined by an angle.
We construct the petal from a `wedge` and a `circle` which we position in such a way that the circle touches the wedge right and left of the circle segment.
 
> petal :: Angle Double -> Diagram B
> petal angle = strokePath $ B.union Winding ( uprightWedge <> touchingCircle)
>   where

First we draw an upright wedge by constructing a counter clockwise wedge starting at 12 o'clock, then rotating it clockwise so it is centered.

>     uprightWedge = wedge 1 yDir angle # rotate (negated halfAngle)

Next, we draw the circle touching the wedge.

>     touchingCircle = circle circleRadius # translateY yShift

The center (origin) of the wedge, the center of the circle and the point where they touch form a right-angled triange with:
             hypothenuse:   Line from center_circle to center_wegde

and relative to half the wedges angle in the origin of the wedge:
             adjacent leg:  radius_wedge
             opposite leg:  radius_circle

thus, cos halfAngle = radius_wedge(=1) / hypothesuse

>     yShift  = 1 / cosA halfAngle

and tan halfAngle = radius_circle / radius_wedge

>     circleRadius = 1 * tanA halfAngle
>     halfAngle = (/2) <$> angle

For the corolla we want n petals arranged in a circle so each has an angle of 1/n times a full circle.

> nPetals n = mconcat $ take n $ iterate (rotate angle) (petal angle)
>  where
>    angle = (1 / fromIntegral n) @@ turn

The seal consists of two corollas on top of each other with a small circle on top of them.

> imperialSeal = circle 0.158
>                <>                                  corolla
>                <> rotateBy (1/ fromIntegral (2*n)) corolla -- background corolla rotated by half a petal
>          where
>             corolla = nPetals n
>             n = 16
>
> imperialSealGoldWhite = imperialSeal # fc gold
>                                      # bgFrame 0.1 white
>
> imperialSealGoldRed = imperialSeal # fc (sRGB24read "#c0a73f")
>                                    # lc (sRGB24read "#be0025")
>                                    # bgFrame 0.1 (sRGB24read "#be0025")
>                                    # lwG 0.04
>                
>
>
> main = mainWith (imperialSealGoldWhite ||| imperialSealGoldRed)

An original alternative just in case

>
> flower =  bgFrame 0.1 white $ circle 0.16 # fc gold
>                            <> corolla     # fc purple
>      where
>        corolla = nPetals 18
>
>
> orangeSlice = bgFrame 0.1 white $  corolla # fc orange # lc white # lwG 0.05
>                                 <> peel
>        where corolla = nPieces 10
>              peel = annularWedge 1.15 1.05 xDir (1 @@ turn) # lw none # fc orange
>
>
> piece :: Angle Double -> Double -- radius of the inner circle
>                       -> Double -- radius of the 2 round corners at the top
>            -> Diagram B
> piece angle inner outer = strokePath $ B.union Winding (uprightWedge <> touchingCircle <> wedgeTop )
>   where
>     uprightWedge = annularWedge (1-outer) inner yDir angle # rotate (negated halfAngle)
>     touchingCircle = circle (circleRadius + 0) # translateY yShift

The center (origin) of the wedge, the center of the circle and the point where they touch form a right-angled triange with:
             hypothenuse:   Line from center_circle to center_wegde

and relative to half the wedges angle in the origin of the wedge:
             adjacent leg:  radius_wedge
             opposite leg:  radius_circle

>     yShift  = inner / cosA halfAngle
>     circleRadius = inner * tanA halfAngle
>     halfAngle = (/2) <$> angle

For rounded edges at the top we draw two circles, and a wedge in the middle.
The circles are located s.t. they touch the arc of the would be sharp corner wedge exactly.

>     wedgeTop = topMiddleWedge <> topLeftCircle <> topRightCircle
>
>     topLeftCircle  = circle outer # translateY (1-outer) # rotate topLeftAngle
>     topRightCircle = circle outer # translateY (1-outer) # rotate (negated topLeftAngle)
>
>     topLeftAlpha = asinA (outer / (1 - outer))
>     topLeftAngle = halfAngle ^-^ topLeftAlpha
>
>     topMiddleWedge = annularWedge 1 (1-outer) yDir width  # rotate (fmap (*(-0.5)) width)
>           where
>              width = angle ^-^ topLeftAlpha ^-^ topLeftAlpha
>
>
>
> nPieces n = mconcat $ take n $ iterate (rotate angle)  (piece (fmap (*0.95) angle) 0.2 0.1)
>  where
>    angle = (1 / fromIntegral n) @@ turn

all4.svg
Reply all
Reply to author
Forward
0 new messages