Circular gray code, like that used on some rotational sensors.
import Diagrams.Backend.SVG.CmdLine
{-# LANGUAGE NoMonomorphismRestriction #-}
import Diagrams.Prelude hiding (gray)
import Data.List.Split (chunksOf)
import Data.Maybe (catMaybes)
import Control.Applicative
import Data.Monoid (mconcat)
import Data.List (transpose)
gray n
recursively generates an n-bit Gray code, where each n-bit
binary number differs from the next in exactly one position.
0 = [[]]
gray = map (False:) g ++ map (True:) (reverse g)
gray n where g = gray (n-1)
Construct a circular diagram from the n-bit gray code: each bit
position corresponds to a concentric ring, with black/white indicating
0/1. ringOffsets
converts a list of booleans into a list of angular
segments corresponding to consecutive runs of True
.
= mkRingsDia . map ringOffsets . transpose . gray $ n
rings n where ringOffsets :: [Bool] -> [(Direction V2 Double, Angle Double)]
= map l2t . chunksOf 2 . findEdges . zip [rotate α xDir | α <- [0 @@ turn, 1/(2^n) @@ turn .. fullTurn]]
ringOffsets = (x, angleBetweenDirs x y)
l2t [x,y] = (x, angleBetweenDirs x xDir) -- arc angle will never be > fullturn ^/ 2
l2t [x]
findEdges :: Eq a => [(Direction V2 Double, a)] -> [Direction V2 Double]
= catMaybes . (zipWith edge <*> tail)
findEdges where edge (_,c1) (a,c2) | c1 /= c2 = Just a
| otherwise = Nothing
Generate concentric circular arcs from lists of angular segments.
= mconcat . zipWith mkRingDia [2,3..]
mkRingsDia where mkRingDia r = lwL 1.05 . mconcat . map (strokeP . scale r . uncurry arc)
= pad 1.1 (rings 10) example
= mainWith (example :: Diagram B) main