]> Git — Sourcephile - julm/worksheets.git/blob - tests/MathSpec.hs
wip
[julm/worksheets.git] / tests / MathSpec.hs
1 {-# LANGUAGE OverloadedLists #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE NoMonomorphismRestriction #-}
4
5 module MathSpec where
6
7 import Data.ByteString.Builder qualified as ByteString.Builder
8 import Data.Colour (Colour)
9 import Data.Colour.Palette.BrewerSet qualified as Brewer
10 import Data.List qualified as List
11 import Data.Text.Short qualified as ShortText
12 import Diagrams.Backend.SVG
13 import Diagrams.Core.Envelope (envelopeS, envelopeV)
14 import Diagrams.Prelude hiding (dot, outer, radius)
15 import Diagrams.TwoD (rotateBy, translateX)
16 import Diagrams.TwoD.Factorization qualified as Factorization
17 import GHC.Conc qualified
18 import Graphics.Svg qualified as SVG
19 import Paths_worksheets qualified as Self
20 import System.Directory qualified as IO
21 import System.FilePath (joinPath, pathSeparator, (<.>), (</>))
22 import System.FilePath.Posix qualified as File
23 import System.IO qualified as IO
24 import Test.Syd (Spec, describe, doNotRandomiseExecutionOrder, goldenByteStringBuilderFile, it, liftIO, withoutRetries)
25 import Text.Blaze.Html5.Attributes qualified as HA
26 import Utils.Tests (goldenPath)
27 import Worksheets.Utils.Prelude
28 import Prelude (pi, sin, sqrt, (/), (^))
29
30 import Math.NumberTheory.Primes (Prime (..), factorise, primes)
31
32 data Config = Config
33 { configName :: String
34 , configUnit :: QDiagram SVG V2 Double Any
35 , configUnitNested :: QDiagram SVG V2 Double Any
36 , configColors :: [Colour Double]
37 , configColors2 :: [Colour Double]
38 , configPack :: Count -> Diag -> Diag -> Diag
39 }
40 config1 =
41 Config
42 { configName = "config1"
43 , configUnit = circle 1 # lw 1 # lc black # fc white
44 , configUnitNested = circle 1 # lw 0 # fc white
45 , configColors = Brewer.brewerSet Brewer.Blues 9 & List.reverse & List.drop 0
46 , configColors2 = Brewer.brewerSet Brewer.Oranges 9 & List.reverse & List.drop 0
47 , configPack = packRings
48 }
49 config2 =
50 Config
51 { configName = "config2"
52 , configUnit = circle 1 # lw 1 # lc black # fc white
53 , configUnitNested = circle 1 # lw 0 # fc white
54 , -- , configColors = Brewer.brewerSet Brewer.Blues 9 & List.drop 2 & evens
55 configColors = Brewer.brewerSet Brewer.Blues 4
56 , configColors2 = Brewer.brewerSet Brewer.Purples 4 & List.reverse
57 , configPack = packRings
58 }
59 config3 =
60 Config
61 { configName = "config3"
62 , configUnit = circle 1 # lw 1 # lc black # fc white
63 , configUnitNested = circle 1 # lw 0 # fc white
64 , -- , configColors = Brewer.brewerSet Brewer.Blues 9 & List.drop 2 & evens
65 configColors = Brewer.brewerSet Brewer.Oranges 4
66 , configColors2 = Brewer.brewerSet Brewer.Reds 4 & List.reverse
67 , configPack = packRings
68 }
69 config4 =
70 Config
71 { configName = "config4"
72 , configUnit = circle 1 # lw 1 # lc black # fc white
73 , configUnitNested = circle 1 # lw 0 # fc white
74 , configColors = Brewer.brewerSet Brewer.Blues 9 & List.reverse & List.drop 2
75 , configColors2 = Brewer.brewerSet Brewer.Reds 9 & List.reverse & List.drop 2
76 , configPack = packRings
77 }
78
79 evens (x : xs) = x : odds xs
80 evens _ = []
81
82 odds (_ : xs) = evens xs
83 odds _ = []
84
85 spec :: HasCallStack => Spec
86 spec = do
87 describe "Math" do
88 describe "Arithmetic" do
89 withoutRetries do
90 doNotRandomiseExecutionOrder do
91 forM_ ([{-config1,config2, config3,-} config4] & list) \config -> do
92 describe (configName config) do
93 -- forM_ (list [1,2,3,4,5,6,7,8,9, 44, 460, 554, 2025]) \n -> do
94 -- numberSpec n (n & primeFactorsAscending) $
95 -- nest2 config $ primeFactorsAscending n
96 -- numberSpec n (n & primeFactorsDescending) $
97 -- nest2 config $ primeFactorsDescending n
98 -- forM_ ([10::Int ..10] & list) \n -> do
99 -- let t = ("multtable."<>show n<>"x"<>show n)
100 -- goldenDiagram t t $
101 -- multtable config n
102 -- describe "num" do
103 -- forM_ ([1..100] & list) \n -> do
104 -- numberSpec n [n] do
105 -- packRings n
106 -- (circle 1 # lw 0 # lc black # fc black)
107 -- (hrule 2 # lc red # lw 1 `atop` circle 1 # lw 0 # fc white)
108 describe "decomp" do
109 threads <- liftIO GHC.Conc.listThreads
110 traceShowM $ threads & List.length
111 forM_ ([20 .. 20] & list) \n -> do
112 numberSpec "" n (primeFactorsDescending n) do
113 factorsDiag config n
114
115 -- numberSpec ".rot90" n (primeFactorsDescending n) do
116 -- factorsDiag config{configPack= \count outer inner -> packRings count outer inner & (# rotate (90@@deg)) } n
117 -- liftIO $ GHC.Conc.listThreads >>= mapM_ GHC.Conc.killThread
118
119 -- goldenDiagram "table" "table" $
120 -- table
121 -- describe "Primes" do
122 -- forM_ (primeDiagrams & List.take 100) \(prim, diag) ->
123 -- numberSpec (prim & unPrime & fromIntegral) diag
124
125 numberSpec :: String -> Int -> [Int] -> QDiagram SVG V2 Double Any -> _
126 numberSpec suffix num facts diag = do
127 let title = show num
128 let name = title <> "." <> List.intercalate "×" (show <$> facts) <> suffix
129 goldenDiagram (title <> suffix) name diag
130
131 fd conf n = nest2 conf $ primeFactorsDescending n
132 factorDiagramDescending conf n = nest2 conf $ primeFactorsDescending n
133
134 -- Factorization.factorDiagram' @Double facts
135
136 goldenDiagram :: String -> String -> QDiagram SVG V2 Double Any -> _
137 goldenDiagram title name diag = do
138 outPath <- goldenPath name "svg"
139 it title do
140 goldenByteStringBuilderFile outPath do
141 -- ExplanationNote: factors from greatest to lowest
142 return $
143 diag
144 & renderDia SVG (SVGOptions (mkWidth 1024) Nothing "" [] True)
145 & SVG.renderBS
146 & ByteString.Builder.lazyByteString
147
148 -----------------------------------------------------------------------------
149
150 -- |
151 -- Module : Diagrams.TwoD.Layout.RingPacking
152 -- Copyright : (c) 2013 Jan Van lent
153 -- License : BSD-style (see LICENSE)
154 -- Maintainer : jakke.vanlent+git@gmail.com
155 --
156 -- More compact versions of the factorization diagrams, as seen at
157 -- <http://mathlesstraveled.com/2012/10/05/factorization-diagrams/>
158 -- and
159 -- <http://mathlesstraveled.com/2012/11/05/more-factorization-diagrams/>
160 --
161 -- The compact layout is achieved by circle in circle packings based on concentric rings.
162 -- The resulting packings are not the most compact, but they have
163 -- more symmetry and the method is very simple.
164 -- The radius of a circle with area equal to that of $n$ unit circles
165 -- is equal to $\sqrt{n}$.
166 -- This can clearly not be achieved if the unit circles are not allowed to
167 -- overlap.
168 -- The compact layout of $n$ unit circles has a bounding radius that scales
169 -- as $\sqrt{8/7 n + O(1)} \approx 1.07 \sqrt{n + O(1)}$.
170 -- The infinite hexagonal packing is the best packing of identical circles
171 -- in the plane.
172 -- For this case, 10% extra area per circle (factor
173
174 -- $\sqrt{12}/\pi \approx 1.10$).
175 -- If we could pack $n$ circles and the 10% extra area perfectly into
176 -- a circle, it would have a radius of about $\sqrt{1.1 n}$ or
177
178 -- $1.05 \sqrt{n}$.
179 --
180 -- The bounding radius of the factorization diagrams scales as $O(n)$,
181 -- because numbers of the form $n=2^p$ are layed out in a linear fashion.
182 -- More compact diagrams are obtained by combining all identical factors.
183 -- E.g. use $72 = 2^3*3^2 = 8*9$ instead of $72 = 2*2*2*3*3$.
184 --
185 -- The main example is "allfactorisations.svg".
186 -- Prime numbers show up as a single compact diagram with only one color.
187 -- Powers of primes show up as a single, less compact diagram with as
188 -- many colors as there are factors.
189 -- For numbers with more than one distinct factor, the results for all
190 -- possible ordering of factors are shown.
191 --
192 -- Even quite big numbers still have reasonably compact factorization
193 -- diagrams as is shown by the example with 2012 and 2013 ("years.svg")
194
195 type Factor = Int
196 type Diag = QDiagram SVG V2 Double Any
197 nest2 :: Config -> [Factor] -> Diag
198 nest2 Config{..} facts =
199 List.zip facts circs
200 & List.foldr
201 (\(fact, outer) inner -> configPack fact outer inner)
202 configUnitNested
203 where
204 circs =
205 [ circle 1 # lw 0 # fc col
206 | col <- configColors
207 ]
208 & (\l -> if null l then [circle 1 # lw 0 # fc green] else l)
209 & List.cycle
210 & List.take (List.length facts + 1)
211 & List.reverse
212
213 -- & List.tail
214 -- & (circle 1 # lw 0 # fc white :)
215
216 factorsDiag conf (n :: Int) =
217 vcat $
218 hcat
219 [ txt (show facts)
220 , nest2 conf facts
221 ]
222 : hcat
223 [ alignedText 0 0 "=" # fontSize 100
224 ]
225 : [ hcat
226 [ txt (show subfacts)
227 , nest2 conf subfacts # scale radius
228 , alignedText 0 0.5 (show radius) # fc green # fontSize 100
229 ]
230 | 1 < List.length facts
231 , (fact, radius) :: (Int, _) <-
232 List.zip facts $
233 facts
234 & List.scanl (\r fact -> r / (ringCountToRingRadius fact + 1)) 1
235 , let subfacts = fact & primeFactorsDescending
236 -- , let facts = factorDiagramDescending conf fact
237 ]
238 where
239 txt t = alignedText 1 0.5 t # fontSize 100
240 facts = n & primeFactorsDescending
241
242 packRings :: Count -> Diag -> Diag -> Diag
243 packRings count outer inner =
244 [ packRing ringCount outer inner
245 | ringCount <- count & partitionRings & List.reverse
246 -- CorrectionNote: reverse to get the inner rings layered ontop of the outer rings
247 ]
248 & mconcat
249
250 -- & (# rotate (90@@deg))
251
252 -- `packRing count outer inner`
253 -- aligns `count` copies of the `inner` diagram along a ring,
254 -- with `outer` scaled to surround those `inner` diagrams.
255 packRing count outer inner = ringCircles <> ringCircum
256 where
257 ringRadius = count & ringCountToRingRadius
258 innerRadius = 1
259 ringRadiusScaled = ringRadius * innerRadius
260 ringCircles =
261 [ inner
262 -- translate horizontaly on the ring
263 # translateX ringRadiusScaled
264 -- rotate along the ring
265 # rotateBy ((fromIntegral i / fromIntegral count))
266 -- scale down to keep it a unit circle
267 # scale (1 / (ringRadiusScaled + innerRadius))
268 <> alignedText 1 0.5 (show (1 / (ringRadiusScaled + innerRadius)))
269 # fontSize 40
270 # fc red
271 | i <- [0 .. count - 1]
272 ]
273 & mconcat
274 ringCircum = outer
275
276 -- | `ringCountToRingRadius n` is the necessary ringRadius
277 -- of a ring of `n` unit circles whose centers are on that ring.
278 --
279 -- See `RefOptimalPackingsForFilledRingsOfCircles`, figure 2.
280 ringCountToRingRadius :: Count -> Double
281 ringCountToRingRadius 0 = 0
282 ringCountToRingRadius 1 = 0
283 ringCountToRingRadius m = 1 / sin (pi / fromIntegral m)
284
285 type Count = Int
286
287 -- | `partitionRings n` is the list of number ringed circles
288 partitionRings :: Factor -> [Count]
289 partitionRings =
290 List.unfoldr
291 \case
292 count
293 | count == 0 -> Nothing
294 | otherwise -> Just (outerCount, count - outerCount)
295 where
296 (_, outerCount) = countToOuterRingCount List.!! count
297
298 countToOuterRingCount :: [(Count, Count)]
299 countToOuterRingCount = 0 & List.unfoldr \n -> Just ((n, go n), n + 1)
300 where
301 go :: Count -> Count
302 go 0 = 0
303 go 1 = 1
304 go n
305 -- ExplanationNote:
306 -- when the outer ring of `n-1` circles (eg. 6)
307 -- can contain the outer ring of the remaining circles (eg. 1),
308 -- the outer ring for `n` circles (eg. 7) can remain the same size.
309 -- Otherwise add
310 | inners `ringFitsIn` prevOuters = prevOuters
311 | otherwise = prevOuters + 1
312 where
313 (_, prevOuters) = countToOuterRingCount List.!! (n - 1)
314 (_, inners) = countToOuterRingCount List.!! (n - prevOuters `max` 0)
315
316 -- | `ringFitsIn inners outers` is `True` iif.
317 -- the circles on a ring of `inners` unit circles are disjoints or tangents
318 -- to the circles on a ring of `outers` unit circles.
319 ringFitsIn :: Count -> Count -> Bool
320 ringFitsIn inners outers
321 | inners <= outers =
322 2 <= ringCountToRingRadius outers - ringCountToRingRadius inners
323 | otherwise = errorShow ("ringFitsIn" :: String, inners, outers)
324
325 {-
326 -- Return
327 partitionRings :: Factor -> [Count]
328 partitionRings =
329 List.unfoldr
330 \case
331 fact | fact == 0 -> Nothing
332 | otherwise -> Just (c, fact - c)
333 where c = ringCount fact
334
335 ringCount :: Factor -> Count
336 ringCount = (fmap go [0::Factor ..] List.!!)
337 where
338 go 0 = 0
339 go 1 = 1
340 go n = outers + increment
341 where
342 outers = ringCount (n - 1)
343 inners = ringCount (n - outers)
344 increment = if inners `ringFitsIn` outers then 0 else 1
345 -}
346
347 ---- equivalent definition
348 -- ringFitsIn 0 _ = True
349 -- ringFitsIn 1 m' = m' >= 6
350 -- ringFitsIn 2 m' = m' >= 10
351 -- ringFitsIn m m' = m' - m >= 7
352
353 nest :: (t1 -> t2 -> t3 -> t3) -> [t1] -> [t2] -> t3 -> t3 -> t3
354 -- nest _pack [] _ d0 d1 = d0
355 -- nest pack (n : ns) (b : bs) d0 d1 = pack n b (nest pack ns bs d1 d1)
356 nest pack ns bs d0 d1 = List.zip ns bs & List.foldr (\(n, b) acc -> pack n b acc) d1
357
358 -- factors = concatMap (uncurry $ flip replicate) . factorise
359 factors n =
360 List.concat
361 [ List.replicate (fromIntegral a) f
362 | (unPrime -> f, a) <- factorise n
363 ]
364
365 -- factors = map (uncurry (^)) . factorise
366 factors' n =
367 [ f ^ a
368 | (unPrime -> f, a) <- factorise n
369 ]
370
371 -- number of prime factors
372 npf = sum . List.map snd . factorise
373
374 -- number of distinct prime factors
375 ndpf = length . factorise
376
377 bagSelect [] = []
378 bagSelect ((x, 1) : b) = (x, b) : [(y, (x, 1) : b') | (y, b') <- bagSelect b]
379 bagSelect ((x, n) : b) = (x, (x, n - 1) : b) : [(y, (x, n) : b') | (y, b') <- bagSelect b]
380
381 -- see also <http://hackage.haskell.org/package/multiset-comb>
382 bagPermutations [] = [[]]
383 bagPermutations b =
384 [ x : ys
385 | (x, b') <- bagSelect b
386 , ys <- bagPermutations b'
387 ]
388
389 factor1 = circle 1 # lw 1 # lc black # fc white
390
391 gdot = circle 1 # lw 0 # fc grey
392 gdots =
393 [ circle 1 # lw 0 # fc col
394 | col <- [grey, white]
395 ]
396 & List.cycle
397 rainbow = [white, red, orange, yellow, green, blue, indigo, violet] & list
398 colDotsBlues = Brewer.brewerSet Brewer.Blues 9 & List.reverse & List.drop 2
399 colDotsOranges = Brewer.brewerSet Brewer.Oranges 9 & List.reverse & List.drop 2
400 colDotsPuOr51 = Brewer.brewerSet Brewer.PuOr 11 & List.take 5 & List.reverse
401 colDotsPuOr52 = Brewer.brewerSet Brewer.PuOr 11 & List.reverse & List.take 5 & List.reverse
402
403 -- main = defaultMain (packRings 20 dots factor1)
404 -- main = defaultMain (packRings 7 (packRings 3 gdot factor1))
405 -- main = defaultMain (nest packRings [7, 5, 3] gdot factor1)
406 numlabel n = text (show n) <> circle 1
407 numbers ns =
408 cat
409 unit_Y
410 [ numlabel n === packRings n (coldots colDotsBlues List.!! (fromIntegral $ npf (n) + 1)) factor1
411 | n <- ns
412 ]
413 primeDiagrams :: [(Prime Int, QDiagram SVG V2 Double Any)]
414 primeDiagrams =
415 [ (n, numlabel n === packRings (unPrime n) gdot factor1)
416 | n <- primes
417 ]
418
419 factorDiagram pack n = nest pack (primeFactorsDescending n)
420 powerFactorDiagram pack n = nest pack $ n & factors' <&> fromIntegral & List.reverse
421
422 primeFactorsAscending = factors >>> fmap fromIntegral
423 primeFactorsDescending = primeFactorsAscending >>> List.reverse
424
425 multtable :: _ => Config -> Int -> QDiagram SVG V2 Double Any
426 multtable conf@Config{..} n =
427 vcat
428 [ hcat
429 [ nest2 conf{configColors = dots} facts # scaleUToY 0.9 <> square 1
430 | let rowFacts = row & primeFactorsAscending
431 , let rowDots = configColors & List.take (List.length rowFacts + 1)
432 , col <- list [1 .. n]
433 , let colFacts = col & primeFactorsAscending
434 , let colDots = configColors2 & List.take (List.length colFacts + 1)
435 , let dots = rowDots <> colDots
436 , let facts = rowFacts <> colFacts
437 ]
438 | row <- list [1 .. n]
439 ]
440
441 coldots cols =
442 [ circle 1 # lw 0 # fc col
443 | col <- white : cols
444 ]
445 & List.cycle
446
447 pfd Config{..} n = powerFactorDiagram packRings n (coldots colDotsBlues) configUnit configUnitNested
448 factorisations ns = cat unit_Y [numlabel n === fd config1 n | n <- ns]
449 powerfactorisations ns = cat unit_Y [numlabel n === pfd config1 n | n <- ns]
450 table =
451 vcat
452 [ hcat
453 [ fd config1 ((10 :: Int) * i + j + 1) # scaleUToY 0.8 <> square 1
454 | j <- list [0 .. 9]
455 ]
456 | i <- list [0 .. 19]
457 ]
458 powertable =
459 vcat
460 [ hcat
461 [ pfd config1 ((10 :: Int) * i + j + 1) # scaleUToY 0.8 <> square 1
462 | j <- list [0 .. 9]
463 ]
464 | i <- list [0 .. 19]
465 ]
466 allfactorisations Config{..} ns =
467 cat
468 unit_Y
469 [ numlabel n
470 === cat
471 unitX
472 [ nest configPack (List.map (fromIntegral . unPrime) p) (coldots colDotsBlues) configUnit configUnitNested
473 | p <- bagPermutations $ factorise n
474 ]
475 | n <- ns
476 ]
477 allpowerfactorisations Config{..} ns =
478 cat
479 unit_Y
480 [ numlabel n
481 === cat
482 unitX
483 [ nest configPack (List.map fromIntegral p) (coldots colDotsBlues) configUnit configUnitNested
484 | p <- List.permutations $ factors' n
485 ]
486 | n <- ns
487 ]
488 years config =
489 ( ( (text "2012" # fc white # fontSize 10)
490 <> (factor1 # scale (sqrt 2012))
491 )
492 ||| (numbers [2012] # centerY)
493 ||| (allfactorisations config $ list [2012 :: Int])
494 # centerY
495 )
496 === ( ( (text "2013" # fc white # fontSize 10)
497 <> (factor1 # scale (sqrt 2013))
498 )
499 ||| (numbers [2013] # centerY)
500 ||| (allfactorisations config $ list [2013 :: Int])
501 # centerY
502 )
503
504 {-
505 --main = defaultMain allfactorisations
506 main = multiMain [ ("numbers", numbers [1..60]),
507 ("primes", primeDiagrams 60),
508 ("years", years),
509 ("factorisations", factorisations [1..60]),
510 ("powerfactorisations", powerfactorisations [1..60]),
511 ("table", table),
512 ("powertable", powertable),
513 ("allfactorisations", allfactorisations [1..60]),
514 ("allpowerfactorisations", allpowerfactorisations [1..60]) ]
515 -}
516
517 data RefOptimalPackingsForFilledRingsOfCircles
518 -- ^ Reference to [Optimal Packings for Filled Rings of Circles](https://doi.org/10.21136/AM.2020.0244-19)
519 -- > [
520 -- > {
521 -- > "DOI": "10.21136/AM.2020.0244-19",
522 -- > "ISSN": "1572-9109",
523 -- > "URL": "https://doi.org/10.21136/AM.2020.0244-19",
524 -- > "abstract": "General circle packings are arrangements of circles on a given surface such that no two circles overlap except at tangent points. In this paper, we examine the optimal arrangement of circles centered on concentric annuli, in what we term rings. Our motivation for this is two-fold: first, certain industrial applications of circle packing naturally allow for filled rings of circles; second, any packing of circles within a circle admits a ring structure if one allows for irregular spacing of circles along each ring. As a result, the optimization problem discussed herein will be extended in a subsequent paper to a more general setting. With this framework in mind, we present properties of concentric rings that have common points of tangency, the exact solution for the optimal arrangement of filled rings along with its symmetry group, and applications to construction of aluminum-conductor steel reinforced cables.",
525 -- > "author": [
526 -- > {
527 -- > "family": "Ekanayake",
528 -- > "given": "Dinesh B."
529 -- > },
530 -- > {
531 -- > "family": "Ranpatidewage",
532 -- > "given": "Manjula Mahesh"
533 -- > },
534 -- > {
535 -- > "family": "LaFountain",
536 -- > "given": "Douglas J."
537 -- > }
538 -- > ],
539 -- > "container-title": "Applications of Mathematics",
540 -- > "id": "Ekanayake2020",
541 -- > "issue": "1",
542 -- > "issued": {
543 -- > "date-parts": [
544 -- > [
545 -- > 2020
546 -- > ]
547 -- > ]
548 -- > },
549 -- > "page": "1-22",
550 -- > "title": "Optimal Packings for Filled Rings of Circles",
551 -- > "type": "article-journal",
552 -- > "volume": "65"
553 -- > }
554 -- > ]