Quest 2: From Complex to Clarity
- Keep top level comments as only solutions, if you want to say something other than a solution put it in a new post. (replies to comments can be whatever)
- You can send code in code blocks by using three backticks, the code, and then three backticks or use something such as https://topaz.github.io/paste/ if you prefer sending it through a URL
Link to participate: https://everybody.codes/
I struggled for a long time because I had nearly the correct results. I had to switch
divwithquot.This puzzle was fun. If you have a visualization, it’s even cooler. (It’s a fractal)
Haskell Code
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE PatternSynonyms #-} {-# OPTIONS_GHC -Wall #-} module Main (main) where import Text.Read (ReadPrec, Read (readPrec)) import Data.Functor ((<&>)) import Data.Text (pattern (:<), Text) import qualified Data.Text as Text import qualified Data.Text.IO as TextIO import Control.Monad ((<$!>)) import Control.Arrow ((<<<)) newtype Complex = Complex (Int, Int) instance Read Complex where readPrec :: ReadPrec Complex readPrec = readPrec <&> \case [a, b] -> Complex (a, b) _ -> undefined instance Show Complex where show :: Complex -> String show (Complex (a, b))= show [a, b] readAEquals :: Text -> Complex readAEquals ('A' :< '=':< rest) = read $ Text.unpack rest readAEquals _ = undefined -- >>> Complex (1, 1) `add` Complex (2, 2) -- [3,3] add :: Complex -> Complex -> Complex (Complex (x1, y1)) `add` (Complex (x2, y2)) = Complex (x1 + x2, y1 + y2) -- >>> Complex (2, 5) `times` Complex (5, 7) -- [-25,-11] times :: Complex -> Complex -> Complex (Complex (x1, y1)) `times` (Complex (x2, y2)) = Complex (x1 * x2 - y1 * y2, x1 * y2 + x2 * y1) dividedBy :: Complex -> Complex -> Complex (Complex (x1, y1)) `dividedBy` (Complex (x2, y2)) = Complex (x1 `quot` x2, y1 `quot` y2) step :: Complex -> Complex -> Complex step a r = let r1 = r `times` r r2 = r1 `dividedBy` Complex (10, 10) r3 = r2 `add` a in r3 zero :: Complex zero = Complex (0, 0) part1 :: Complex -> Complex part1 a = iterate (step a) (Complex (0, 0)) !! 3 shouldBeEngraved :: Complex -> Bool shouldBeEngraved complexPoint = let cycleStep :: Complex -> Complex -> Complex cycleStep point r = let r2 = r `times` r r3 = r2 `dividedBy` Complex (100000, 100000) in point `add` r3 inRange x = x <= 1000000 && x >= -1000000 in all (\ (Complex (x, y)) -> inRange x && inRange y) <<< take 101 <<< iterate (cycleStep complexPoint) $ zero -- >>> shouldBeEngraved $ Complex (35630,-64880) -- True -- >>> shouldBeEngraved $ Complex (35460, -64910) -- False -- >>> shouldBeEngraved $ Complex (35630, -64830) -- False part2 :: Complex -> Int part2 (Complex (xA, yA)) = let xB = xA + 1000 yB = yA + 1000 in length . filter shouldBeEngraved $ do x <- [xA, xA+10.. xB] y <- [yA, yA+10.. yB] pure $ Complex (x, y) part3 :: Complex -> Int part3 (Complex (xA, yA)) = length . filter shouldBeEngraved $ do x <- [xA..xA+1000] y <- [yA..yA+1000] pure $ Complex (x, y) -- >>> [0, 10..100] -- [0,10,20,30,40,50,60,70,80,90,100] main :: IO () main = do a <- readAEquals <$!> TextIO.getContents print $ part1 a print $ part2 a print $ part3 aMy girlfriend is learning python, we are taking on the challenges together, today I may upload her solution:
python
A=[-3344,68783] R = [0, 0] B= [A[0]+1000, A[1]+1000] pointsengraved = 0 cycleright = 0 for i in range(A[1], B[1]+1): for j in range(A[0], B[0]+1): for k in range(100): R = [int(R[0] * R[0] - R[1] * R[1]), int(R[0] * R[1] + R[1] * R[0])] R = [int(R[0] / 100000), int(R[1] / 100000)] R = [int(R[0] + j), int(R[1] + i)] if -1000000>R[0] or R[0]>1000000 or -1000000>R[1] or R[1]>1000000: #print(".", end="") break cycleright += 1 if cycleright == 100: pointsengraved += 1 #print("+", end="") cycleright = 0 R = [0, 0] #print() print(pointsengraved)The commented out print statements produce an ascii map of the set, which can be cool to view at the right font size.
For quest 2, I decided to implement my own Complex type and operators, because I expected parts 2 and 3 to have something unconventional, but alas it’s just a regular Mandelbrot fractal.
Nim again, Nim forever:
type Complex = tuple[x,y: int] proc `$`(c: Complex): string = &"[{c.x},{c.y}]" proc `+`(a,b: Complex): Complex = (a.x+b.x, a.y+b.y) proc `-`(a,b: Complex): Complex = (a.x-b.x, a.y-b.y) proc `*`(a,b: Complex): Complex = (a.x*b.x - a.y*b.y, a.x*b.y + a.y*b.x) proc `/`(a,b: Complex): Complex = (a.x div b.x, a.y div b.y) proc `/`(a: Complex, b: int): Complex = (a.x div b, a.y div b) proc parseInput(input: string): Complex = let parts = input.split({'=','[',',',']'}) (parseInt(parts[2]), parseInt(parts[3])) proc isStable(point: Complex, iter: int): bool = var num: Complex for _ in 1..iter: num = (num * num) / 100_000 + point if num.x notin -1_000_000 .. 1_000_000 or num.y notin -1_000_000 .. 1_000_000: return false true proc solve_part1*(input: string): Solution = let start = parseInput(input) var point: Complex for _ in 1..3: point = (point * point) / 10 + start result := $point proc solve_part2*(input: string): Solution = let start = parseInput(input) for y in 0..100: for x in 0..100: let point: Complex = (start.x + 10 * x, start.y + 10 * y) if point.isStable(iter=100): inc result.intVal proc solve_part3*(input: string): Solution = let start = parseInput(input) for y in 0..1000: for x in 0..1000: let point: Complex = (start.x + x, start.y + y) if point.isStable(iter=100): inc result.intValFull solution at Codeberg: solution.nim
FSharp
(my first submission failed, so I may not be as detailed here)I laugh at how long this took me. At first I got stuck due to checked arithmetic. In FSharp you open the
Checkedmodule and you get the overloaded operators for primitives, whereas CSharp ischecked {a + b}. I also mistakenly useddistincton part 3 when I didn’t need it.I did appreciate the
choosefunctions of functional programming, which returns all of theSomevalues of a sequence of options. The PSeq library let me use 70% of the cpu on the calculations :)module EveryBodyCodes2025.Quest02 open System.IO open System.Text.RegularExpressions open FSharp.Collections.ParallelSeq open Checked [<Struct>] type ComplexNumber = {X: int64; Y: int64} static member (+) (a: ComplexNumber, b: ComplexNumber) = {X = a.X + b.X; Y = a.Y + b.Y } static member (*) (a: ComplexNumber, b: ComplexNumber) = { X = ( a.X * b.X ) - (a.Y * b.Y); Y = (a.X * b.Y) + (a.Y * b.X) } static member (/) (a: ComplexNumber, b: ComplexNumber) = { X = a.X / b.X; Y = a.Y / b.Y } override this.ToString() = $"[{this.X},{this.Y}]" let parseInput file = File.ReadAllLines file |> fun lines -> let reg = Regex(@"A=\[(-?\d+),(-?\d+)\]") let res = reg.Match(lines[0]) match res.Success with | true -> let x = int64 res.Groups[1].Value let y = int64 res.Groups[2].Value {X = x; Y = y} | false -> failwith "failed to parse" let part1 () = parseInput "Inputs/Quest02/Q02_P01.txt" |> fun a -> [1..3] |> List.fold (fun acc _ -> (acc * acc) / { X = 10; Y = 10 } + a ) {X = 0; Y = 0} let cycle p = let rec iterate current iteration = if iteration = 100 then Some current else let next = (current * current) / {X = 100_000; Y = 100_000 } + p if abs(next.X) > 1_000_000 || abs(next.Y) > 1_000_000 then None else iterate next (iteration + 1) iterate { X = 0; Y = 0 } 0 let part2 () = parseInput "Inputs/Quest02/Q02_P02.txt" |> fun a -> seq { for y in 0..100 do for x in 0..100 do yield {X = a.X + (int64 x * 10L); Y = a.Y + (int64 y * 10L)} } |> PSeq.choose cycle |> PSeq.distinct |> PSeq.length let part3 () = parseInput "Inputs/Quest02/Q02_P03.txt" |> fun a -> seq { for y in 0..1000 do for x in 0..1000 do yield {X = a.X + (int64 x); Y = a.Y + (int64 y)} } |> PSeq.choose cycle |> PSeq.lengthIt’s gradually coming back to me. The Haskell Complex type doesn’t work particularly nicely as an integer, plus the definition of division is more like “scale”, so I just went with my own type.
Then I forgot which of
divandquotI should use, and kept getting nearly the right answer :/import Data.Ix data CNum = CNum !Integer !Integer instance Show CNum where show (CNum x y) = "[" ++ show x ++ "," ++ show y ++ "]" cadd, cmul, cdiv :: CNum -> CNum -> CNum (CNum x1 y1) `cadd` (CNum x2 y2) = CNum (x1 + x2) (y1 + y2) (CNum x1 y1) `cmul` (CNum x2 y2) = CNum (x1 * x2 - y1 * y2) (x1 * y2 + y1 * x2) (CNum x1 y1) `cdiv` (CNum x2 y2) = CNum (x1 `quot` x2) (y1 `quot` y2) part1 a = iterate op (CNum 0 0) !! 3 where op x = ((x `cmul` x) `cdiv` CNum 10 10) `cadd` a countEngraved = length . filter engrave where engrave p = let rs = take 100 $ tail $ iterate (op p) (CNum 0 0) in all (\(CNum x y) -> abs x <= 1000000 && abs y <= 1000000) rs op p r = ((r `cmul` r) `cdiv` CNum 100000 100000) `cadd` p part2 a = countEngraved . map (\(y, x) -> a `cadd` CNum (x * 10) (y * 10)) $ range ((0, 0), (100, 100)) part3 a = countEngraved . map (\(y, x) -> a `cadd` CNum x y) $ range ((0, 0), (1000, 1000)) main = do print $ part1 $ CNum 164 56 print $ part2 $ CNum (-21723) 67997 print $ part3 $ CNum (-21723) 67997Then I forgot which of div and quot I should use, and kept getting nearly the right answer
That sounds amazingly infuriating! and hard to debug. I totally feel you there.
Rust
use log::debug; use std::collections::HashSet; use regex::Regex; #[derive(PartialEq, Eq, Hash, Clone)] struct Number(isize, isize); impl Number { fn add(self: &Number, b: &Number) -> Number { Number(self.0 + b.0, self.1 + b.1) } fn mul(self: &Number, b: &Number) -> Number { Number(self.0 * b.0 - self.1 * b.1, self.0 * b.1 + self.1 * b.0) } fn div(self: &Number, b: &Number) -> Number { Number(self.0 / b.0, self.1 / b.1) } } pub fn solve_part_1(input: &str) -> String { let re = Regex::new(r"A=\[(\d+),(\d+)\]").unwrap(); let (_, [x, y]) = re.captures(input).unwrap().extract(); let a = Number(x.parse().unwrap(), y.parse().unwrap()); let mut res = Number(0, 0); for _ in 0..3 { res = res.mul(&res); res = res.div(&Number(10, 10)); res = res.add(&a); } format!("[{},{}]", res.0, res.1) } pub fn solve_part_2(input: &str) -> String { let re = Regex::new(r"A=\[([-0-9]+),([-0-9]+)\]").unwrap(); let (_, [x, y]) = re.captures(input).unwrap().extract(); let a = Number(x.parse().unwrap(), y.parse().unwrap()); let mut engraved_points = 0; let mut pts: HashSet<_> = HashSet::new(); for i in 0..=100 { for j in 0..=100 { let pt = Number(a.0 + 10 * i, a.1 + 10 * j); let mut res = Number(0, 0); engraved_points += 1; pts.insert(pt.clone()); for _ in 0..100 { res = res.mul(&res); res = res.div(&Number(100_000, 100_000)); res = res.add(&pt); if res.0.abs() > 1_000_000 || res.1.abs() > 1_000_000 { engraved_points -= 1; pts.remove(&pt); break; } } } } for i in 0..=100 { debug!("{}", (0..=100).map(|j| if pts.contains(&Number(a.0 + 10*i, a.1 + 10*j)) { 'X' } else {'.'}).collect::<String>()); } engraved_points.to_string() } pub fn solve_part_3(input: &str) -> String { let re = Regex::new(r"A=\[([-0-9]+),([-0-9]+)\]").unwrap(); let (_, [x, y]) = re.captures(input).unwrap().extract(); let a = Number(x.parse().unwrap(), y.parse().unwrap()); let mut engraved_points = 0; for i in 0..=1000 { for j in 0..=1000 { let pt = Number(a.0 + i, a.1 + j); let mut res = Number(0, 0); engraved_points += 1; for _ in 0..100 { res = res.mul(&res); res = res.div(&Number(100_000, 100_000)); res = res.add(&pt); if res.0.abs() > 1_000_000 || res.1.abs() > 1_000_000 { engraved_points -= 1; break; } } } } engraved_points.to_string() }



