~rootmos/AoC

144323cb02102a05034e7b88e01360c1280a2b6d — Gustav Behm 1 year, 11 months ago 52bb130
Add solution to AoC 2022 #14a
4 files changed, 286 insertions(+), 1 deletions(-)

A 2022/14.example
A 2022/14.hs
A 2022/14.input
M lib/Qulude.hs
A 2022/14.example => 2022/14.example +2 -0
@@ 0,0 1,2 @@
498,4 -> 498,6 -> 496,6
503,4 -> 502,4 -> 502,9 -> 494,9

A 2022/14.hs => 2022/14.hs +128 -0
@@ 0,0 1,128 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Main where

import Qulude

--import Data.Array ( (!) )
import qualified Data.Array as Array
import qualified Data.Array.ST as STArray
import qualified Data.Either as Either
import qualified Data.List as List
--import Data.Array ( (!) )
import qualified Data.Map as Map
import qualified Data.Maybe as Maybe
import qualified Data.Sequence as Seq
import qualified Data.Set as Set

data Segment = Horizontal (Int, Int) Int
             | Vertical Int (Int, Int)
  deriving ( Show, Eq )

type Line = [ Segment ]

type Parse = [ Line ]
parser :: Parser Parse
parser = many $ line <* newline
  where point = do
          x <- int
          char ','
          y <- int
          return (x,y)
        line = mk [] <$> (point `sepBy` string " -> ")
        mk acc (_:[]) = acc
        mk acc ((x0,y0):p@(x1,y1):ps) | x0 == x1 = mk (Vertical x0 (f y0 y1):acc) (p:ps)
        mk acc ((x0,y0):p@(x1,y1):ps) | y0 == y1 = mk (Horizontal (f x0 x1) y0:acc) (p:ps)
        f a b | a <= b = (a, b)
        f a b | a > b = (b, a)

bounds :: [ Line ] -> ((Int, Int), (Int, Int))
bounds = f (0, 500, 500)
  where f (y, x0, x1) [] = ((x0, 0), (x1, y))
        f st (l:ls) = f (g st l) ls
        g st [] = st
        g st (s:ss) = g (h st s) ss
        h (y, x0, x1) (Horizontal (x0', x1') y') = (max y y', min x0 x0', max x1 x1')
        h (y, x0, x1) (Vertical x (_, y1')) = (max y y1', min x x0, max x x1)

data Point = Rock | Air | Sand
  deriving ( Show, Eq )

isBlocked Rock = True
isBlocked Sand = True
isBlocked Air = False

type Cave s = STArray s (Int, Int) Point

initialCave :: [ Line ] -> ST s (Cave s)
initialCave ls = STArray.newArray (bounds ls) Air >>= flip f ls
  where f c [] = return c
        f c (l:ls) = g c l >> f c ls
        g c [] = return ()
        g c (s:ss) = h c s >> g c ss
        h c (Horizontal (x0, x1) y) = do
          STArray.writeArray c (x0, y) Rock
          if (x0 /= x1) then h c (Horizontal (succ x0, x1) y) else return ()
        h c (Vertical x (y0, y1)) = do
          STArray.writeArray c (x, y0) Rock
          if (y0 /= y1) then h c (Vertical x (succ y0, y1)) else return ()

draw :: Cave s -> ST s [String]
draw c = do
  ((x0,y0), (x1,y1)) <- STArray.getBounds c
  sequence $ [ row y x0 x1 | y <- [y0..y1] ]
    where row y x0 x1 = sequence [ p <$> STArray.readArray c (x,y) | x <- [x0..x1] ]
          p Air = '.'
          p Rock = '#'
          p Sand = 'o'

drawUnsafe :: [String] -> ()
drawUnsafe ls = unsafePerformIO $ do
  putStrLn ""
  sequence_ $ fmap putStrLn ls

produce :: Cave s -> ST s Bool
produce c = step (500, 0)
  where down (x,y) = f (x, succ y)
        left (x,y) = f (pred x, succ y)
        right (x,y) = f (succ x, succ y)
        f p = do
          bs <- STArray.getBounds c
          if Array.inRange bs p
             then do
               t <- STArray.readArray c p
               return . Just $ if isBlocked t then Nothing else Just p
             else return Nothing
        step p = do
          [d, l, r] <- sequence [down p, left p, right p]
          case (d, l, r) of
            (Nothing, _, _) -> return False
            (_, Nothing, _) -> return False
            (_, _, Nothing) -> return False
            (Just (Just q), _, _) -> step q
            (_, Just (Just q), _) -> step q
            (_, _, Just (Just q)) -> step q
            (Just Nothing, Just Nothing, Just Nothing) -> do
              STArray.writeArray c p Sand
              return True

partA :: Parse -> Int
partA ls = runST $ do
  c <- initialCave ls
  loop 0 c
    where loop n c = do
            t <- produce c
            if t then loop (succ n) c else return n

--partB :: Parse -> Parse
--partB = id

main :: IO ()
main = with parser $ do
  run' "14.example" "a example" partA 24
  run' "14.input" "a input" partA 832
  --run "14.example" "b example" partB
  --run "14.input" "b input" partB

A 2022/14.input => 2022/14.input +148 -0
@@ 0,0 1,148 @@
481,122 -> 481,125 -> 476,125 -> 476,129 -> 491,129 -> 491,125 -> 485,125 -> 485,122
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
489,148 -> 493,148
471,152 -> 475,152
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
492,60 -> 492,63 -> 486,63 -> 486,71 -> 502,71 -> 502,63 -> 496,63 -> 496,60
504,158 -> 504,162 -> 503,162 -> 503,170 -> 511,170 -> 511,162 -> 507,162 -> 507,158
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
486,146 -> 490,146
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
504,158 -> 504,162 -> 503,162 -> 503,170 -> 511,170 -> 511,162 -> 507,162 -> 507,158
518,31 -> 518,35 -> 517,35 -> 517,38 -> 529,38 -> 529,35 -> 522,35 -> 522,31
490,100 -> 495,100
481,122 -> 481,125 -> 476,125 -> 476,129 -> 491,129 -> 491,125 -> 485,125 -> 485,122
500,141 -> 505,141
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
518,31 -> 518,35 -> 517,35 -> 517,38 -> 529,38 -> 529,35 -> 522,35 -> 522,31
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
495,57 -> 499,57
489,133 -> 489,134 -> 494,134
488,106 -> 493,106
519,57 -> 523,57
481,122 -> 481,125 -> 476,125 -> 476,129 -> 491,129 -> 491,125 -> 485,125 -> 485,122
493,141 -> 498,141
504,54 -> 508,54
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
474,150 -> 478,150
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
498,54 -> 502,54
489,139 -> 494,139
518,31 -> 518,35 -> 517,35 -> 517,38 -> 529,38 -> 529,35 -> 522,35 -> 522,31
510,41 -> 510,42 -> 521,42 -> 521,41
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
480,150 -> 484,150
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
518,31 -> 518,35 -> 517,35 -> 517,38 -> 529,38 -> 529,35 -> 522,35 -> 522,31
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
504,158 -> 504,162 -> 503,162 -> 503,170 -> 511,170 -> 511,162 -> 507,162 -> 507,158
501,51 -> 505,51
504,158 -> 504,162 -> 503,162 -> 503,170 -> 511,170 -> 511,162 -> 507,162 -> 507,158
498,104 -> 503,104
477,148 -> 481,148
510,48 -> 514,48
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
483,152 -> 487,152
492,60 -> 492,63 -> 486,63 -> 486,71 -> 502,71 -> 502,63 -> 496,63 -> 496,60
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
492,60 -> 492,63 -> 486,63 -> 486,71 -> 502,71 -> 502,63 -> 496,63 -> 496,60
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
516,54 -> 520,54
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
494,102 -> 499,102
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
504,158 -> 504,162 -> 503,162 -> 503,170 -> 511,170 -> 511,162 -> 507,162 -> 507,158
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
518,31 -> 518,35 -> 517,35 -> 517,38 -> 529,38 -> 529,35 -> 522,35 -> 522,31
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
513,51 -> 517,51
492,60 -> 492,63 -> 486,63 -> 486,71 -> 502,71 -> 502,63 -> 496,63 -> 496,60
481,122 -> 481,125 -> 476,125 -> 476,129 -> 491,129 -> 491,125 -> 485,125 -> 485,122
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
518,31 -> 518,35 -> 517,35 -> 517,38 -> 529,38 -> 529,35 -> 522,35 -> 522,31
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
489,133 -> 489,134 -> 494,134
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
507,57 -> 511,57
492,60 -> 492,63 -> 486,63 -> 486,71 -> 502,71 -> 502,63 -> 496,63 -> 496,60
504,158 -> 504,162 -> 503,162 -> 503,170 -> 511,170 -> 511,162 -> 507,162 -> 507,158
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
477,152 -> 481,152
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
480,146 -> 484,146
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
510,54 -> 514,54
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
460,155 -> 474,155 -> 474,154
495,152 -> 499,152
492,60 -> 492,63 -> 486,63 -> 486,71 -> 502,71 -> 502,63 -> 496,63 -> 496,60
507,45 -> 511,45
499,27 -> 499,28 -> 519,28
495,106 -> 500,106
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
510,41 -> 510,42 -> 521,42 -> 521,41
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
492,60 -> 492,63 -> 486,63 -> 486,71 -> 502,71 -> 502,63 -> 496,63 -> 496,60
481,122 -> 481,125 -> 476,125 -> 476,129 -> 491,129 -> 491,125 -> 485,125 -> 485,122
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
504,48 -> 508,48
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
492,150 -> 496,150
502,106 -> 507,106
486,150 -> 490,150
489,152 -> 493,152
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
481,122 -> 481,125 -> 476,125 -> 476,129 -> 491,129 -> 491,125 -> 485,125 -> 485,122
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
492,137 -> 497,137
507,51 -> 511,51
504,158 -> 504,162 -> 503,162 -> 503,170 -> 511,170 -> 511,162 -> 507,162 -> 507,158
484,104 -> 489,104
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
518,31 -> 518,35 -> 517,35 -> 517,38 -> 529,38 -> 529,35 -> 522,35 -> 522,31
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
460,155 -> 474,155 -> 474,154
487,102 -> 492,102
491,104 -> 496,104
481,122 -> 481,125 -> 476,125 -> 476,129 -> 491,129 -> 491,125 -> 485,125 -> 485,122
510,41 -> 510,42 -> 521,42 -> 521,41
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
483,148 -> 487,148
501,57 -> 505,57
496,139 -> 501,139
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
481,106 -> 486,106
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
475,119 -> 475,113 -> 475,119 -> 477,119 -> 477,113 -> 477,119 -> 479,119 -> 479,114 -> 479,119 -> 481,119 -> 481,115 -> 481,119 -> 483,119 -> 483,113 -> 483,119
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
490,23 -> 490,13 -> 490,23 -> 492,23 -> 492,17 -> 492,23 -> 494,23 -> 494,18 -> 494,23 -> 496,23 -> 496,22 -> 496,23 -> 498,23 -> 498,21 -> 498,23 -> 500,23 -> 500,18 -> 500,23 -> 502,23 -> 502,15 -> 502,23 -> 504,23 -> 504,22 -> 504,23 -> 506,23 -> 506,18 -> 506,23 -> 508,23 -> 508,19 -> 508,23
494,97 -> 494,92 -> 494,97 -> 496,97 -> 496,91 -> 496,97 -> 498,97 -> 498,88 -> 498,97 -> 500,97 -> 500,94 -> 500,97
486,141 -> 491,141
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
499,27 -> 499,28 -> 519,28
499,84 -> 499,80 -> 499,84 -> 501,84 -> 501,77 -> 501,84 -> 503,84 -> 503,75 -> 503,84 -> 505,84 -> 505,83 -> 505,84
513,57 -> 517,57
483,144 -> 487,144

M lib/Qulude.hs => lib/Qulude.hs +8 -1
@@ 26,6 26,7 @@ module Qulude ( module Prelude

              , count
              , distinct
              , combine

              , thrush
              , warbler


@@ 50,6 51,7 @@ module Qulude ( module Prelude
              , unsafePerformIO

              , Array
              , STArray, STUArray
              , Map
              , Set



@@ 71,6 73,7 @@ import Data.Functor.Identity
import Data.Word

import Data.Array ( Array )
import Data.Array.ST ( STArray, STUArray )
import Data.Map ( Map )
import Data.Sequence ( Seq )



@@ 81,7 84,7 @@ import Debug.Trace

import Control.Monad.State
import Control.Monad.Reader
import Text.Parsec hiding ( State, count )
import Text.Parsec hiding ( State, Line, count )
import Text.Printf

import Control.Monad.ST


@@ 120,6 123,10 @@ count = go 0
distinct :: Ord a => [a] -> [a]
distinct = Set.toList . Set.fromList

combine :: [a] -> [a] -> [a]
combine [] bs = bs
combine (a:as) bs = a:(combine as bs)

fromEither :: Either a a -> a
fromEither (Left a) = a
fromEither (Right a) = a