W. Kolmyjec’s Hex Variation
import Diagrams.Backend.SVG.CmdLine
This is a transcription in Haskell of “Hex Variation” by William Kolmyjec. The algorithm itself is inspired by the version of Steve Berrick, from the Recode project.
{-# LANGUAGE NoMonomorphismRestriction #-}
import Diagrams.Prelude
import System.Random
We first define the parameters of the tile, which is hexagonal. The side of a hexagon is the radius of its circumscribed circle, here taken as 1.
The apothem is the distance from the center to the side:
= sqrt(3)/2 h
We define the difference between the radius and the apothem:
= cos(pi/3) h'
We then define a tile. The hexagon is not actually shown but inside are two arcs, along with a vertical line. To see the tiling, you can add an hexagon in the list below:
hexagon' :: Diagram B
= mconcat [arc1 # translateX (-1)
hexagon' 2*h)
, vrule (# rotateBy (1/2) # translateX 1
, arc1
]where
= arc' 0.5 (xDir # rotate (-pi/3 @@ rad)) (2*pi/3 @@ rad) arc1
In the final tiling, the tiles will be rotated randomly with angles in \(\{0, \frac{2 \pi}{3}, \frac{4 \pi}{3} \}\).
rotateHexagon' :: Int -> Diagram B
= hexagon' # rotate (n'*2*pi/3 @@ rad)
rotateHexagon' n where
= fromIntegral n n'
The tiling is created from a list of centers, defined here:
centerPosition :: Int -> Int -> (Double, Double)
centerPosition x y| (x `mod` 2 == 0) = ((2-h')*x', 2*y'*h)
| otherwise = ((2-h')*x', (2*y'-1)*h)
where
= fromIntegral x
x' = fromIntegral y y'
The function generating random angles with a fixed seed:
generateAngles :: [Int]
= randomRs (0, 2) (mkStdGen 31) generateAngles
Finally, the tiling is created here:
hexVariation :: Diagram B
= position (zip (map p2 pos) (map rotateHexagon' angles))
hexVariation where
= [(centerPosition x y) | x <- [0..nb-1], y <- [0..nb-1]]
pos = take ((nb+1)*(nb+1)) $ generateAngles angles
The envelope of our tiling is nb*1.5*side + 0.5*side
in width and nb*2*h+h
in
height. We remove the “corners” to avoid “holes” at the borders of the figure
and define the new width and height:
= nb*1.5 - 0.5
width' = nb*2*h - h height'
Which are used to “clip” the figure here:
= 12
nb example :: Diagram B
= hexVariation # center # rectEnvelope x0 u0 # rotateBy (1/4)
example where
= p2 (-width'/2, -height'/2)
x0 = r2 (width', height') u0
= mainWith (example :: Diagram B) main