Brent Yorgey

{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE TypeFamilies              #-}

module CreatingSymmetry where

import           Control.Monad                       (replicateM)
import           Control.Monad.Random
import           Data.Colour.Palette.ColorSet        (Brightness (..),
                                                      d3Colors2)
import           Data.Complex
import           Data.List.Split                     (chunksOf)
import           Diagrams.Backend.Rasterific.CmdLine
import           Diagrams.Prelude

type Term = (Complex Double, Int)
type Params = [Term]

-- | Draw the parametric curve in the complex plane f(t) = \sum_{j=1}^M a_j e^{n_j i t} .
drawCyclicCurve :: (TrailLike t, N t ~ Double, V t ~ V2) => Params -> t
drawCyclicCurve = drawCyclicCurve' 360

-- | Draw the parametric curve in the complex plane f(t) =
--   \sum_{j=1}^M a_j e^{n_j i t}.  The first argument controls the
--   number of sample points to generate.
drawCyclicCurve' :: (TrailLike t, N t ~ Double, V t ~ V2) => Int -> Params -> t
drawCyclicCurve' samples params
  = cubicSpline True (map (eval params) [0, incr .. tau - incr])
  where
    incr = tau / fromIntegral samples
    eval params t = c2p . sum . map (evalComponent t) $ params

c2p :: Complex a -> P2 a
c2p (x :+ y) = (x ^& y)

evalComponent :: Double -> Term -> Complex Double
evalComponent t (a,n) = a * cis (fromIntegral n * t)

drawCircles :: Params -> Double -> Diagram B
drawCircles params t = drawCircles' (zip [0..] params) t
  where
    drawCircles' [] _ = circle 0.05 # lw none # fc red
    drawCircles' ((i,(a,n)):params) t
      = drawCircles' params t # moveTo (c2p a # rotate theta)
        <> (circle (magnitude a) <> (origin ~~ c2p a)) # lc (d3Colors2 Light i) # rotate theta
      where
        theta = (t * fromIntegral n) @@ rad

randomCurve :: (MonadRandom m, Applicative m) => m Params
randomCurve = do
  numComponents <- getRandomR (2, 4)
  replicateM numComponents randomComponent

randomComponent :: (MonadRandom m, Applicative m) => m (Complex Double, Int)
randomComponent = (,) <$> ((:+) <$> getRandomR (-1,1) <*> getRandomR (-1,1)) <*> getRandomR (-30,30)

mysteryCurve :: Diagram B
mysteryCurve = drawCyclicCurve mysteryParams

mysteryParams :: Params
mysteryParams = [(1,1), (1/2, 6), (0 :+ 1/3, -14)]

randomCurves :: Int -> IO (Diagram B)
randomCurves n = do
  curves <- evalRandIO $ replicateM n randomCurve
  return
    $ vsep 1 . map (hsep 1) . chunksOf 5
    . map ( beneath (square 4 # lw none)
          . centerXY . sized (dims2D 4 4) . drawCyclicCurve)
    $ curves

main = mainWith $ zip (map (bg' white . frame 0.5 . withEnvelope bb) frames)
                      (repeat (3 :: Int))

bg' :: Colour Double -> Diagram B -> Diagram B
bg' c d = (d <> r # lw none # fc c # scale 1.1) # withEnvelope r
  where
    r = boundingRect d

bb = mconcat . (map boundingBox) $ frames

frames =
  [ mconcat [ drawCircles mysteryParams (fromIntegral t * tau / fromIntegral numFrames)
            , mysteryCurve
            ]
  | t <- [0 .. numFrames - 1]
  ]

numFrames :: Int
numFrames = 720

3 thoughts on “Brent Yorgey

  1. shinichi Post author

    Random cyclic curves

    by Brent Yorgey

    The Math Less Traveled

    http://mathlesstraveled.com/2015/06/04/random-cyclic-curves-5/

    Princeton Press just sent me a review copy of a new book by Frank Farris called Creating Symmetry: The Artful Mathematics of Wallpaper Patterns. It looks amazing and I’m super excited to read it. Apparently John Cook has been reading it as well, and posted some Python code for generating this curve, which shows up towards the beginning of the book:

    Mike Croucher also posted an interactive version using Jupyter notebook, where you can play with sliders to control the parameters of the curve and watch it evolve.

    This is a plot of the parametric equation

    f(t) = e^{it} + \frac{1}{2} e^{6it} + \frac{i}{3} e^{-14it}

    in the complex plane. In general, Farris considers parametric equations of the form

    f(t) = \sum_j a_j e^{n_j it},

    where a_j are complex numbers, n_j are integers, and as usual i = \sqrt{-1}. All such equations correspond to cyclic plots in the complex plane; he analyzes what sorts of symmetry they will have based on the parameters n_j.

    He also spends some time talking about the aesthetics of picking values for a_j and n_j that result in beautiful curves. Instead of making carefully considered choices in this kind of situations, I often like to employ randomness to just generate a bunch of different instantiations and see what comes up (although there is still a certain amount of art in choosing the distributions for the random parameters). So, here are 50 random curves. Each one has

    • Either 2, 3, or 4 terms
    • Exponents chosen uniformly at random from [-30, 30]
    • Coefficients chosen uniformly at random from the square in the complex plane from -1 - i to 1 + i.

    I really like seeing these all together. They are not all great individually, but as a group, it’s fun seeing their differences, similarities, and idiosyncracies.

    Don’t ask me what the parameters are for an individual curve because the program I used to generate them does not save the parameters anywhere! The code is here if you want to see it; of course it is written in Haskell and uses the diagrams framework.

    Reply
  2. shinichi Post author

    Creating Symmetry:
    The Artful Mathematics of Wallpaper Patterns

    by Frank A. Farris

    http://press.princeton.edu/titles/10435.html

    FarrisThis lavishly illustrated book provides a hands-on, step-by-step introduction to the intriguing mathematics of symmetry. Instead of breaking up patterns into blocks—a sort of potato-stamp method—Frank Farris offers a completely new waveform approach that enables you to create an endless variety of rosettes, friezes, and wallpaper patterns: dazzling art images where the beauty of nature meets the precision of mathematics.

    Featuring more than 100 stunning color illustrations and requiring only a modest background in math, Creating Symmetry begins by addressing the enigma of a simple curve, whose curious symmetry seems unexplained by its formula. Farris describes how complex numbers unlock the mystery, and how they lead to the next steps on an engaging path to constructing waveforms. He explains how to devise waveforms for each of the 17 possible wallpaper types, and then guides you through a host of other fascinating topics in symmetry, such as color-reversing patterns, three-color patterns, polyhedral symmetry, and hyperbolic symmetry. Along the way, Farris demonstrates how to marry waveforms with photographic images to construct beautiful symmetry patterns as he gradually familiarizes you with more advanced mathematics, including group theory, functional analysis, and partial differential equations. As you progress through the book, you’ll learn how to create breathtaking art images of your own.

    Fun, accessible, and challenging, Creating Symmetry features numerous examples and exercises throughout, as well as engaging discussions of the history behind the mathematics presented in the book.

    Reply

Leave a Reply

Your email address will not be published. Required fields are marked *