Day 4: Printing Department

Megathread guidelines

  • 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

FAQ

  • VegOwOtenks@lemmy.world
    link
    fedilink
    arrow-up
    5
    ·
    2 days ago

    Haskell

    I tried rewriting part 2 to use a MutableArray, but it only made everything slower. So I left it at this. I saw somebody do a 1-second-challenge last year and I feel like that will be very hard unless I up my performance game.

    Solution, Both Parts
    {-# LANGUAGE OverloadedStrings #-}
    {-# OPTIONS_GHC -Wall #-}
    module Main (main) where
    import qualified Data.Text as Text
    import Data.Array.Unboxed (UArray)
    import qualified Data.Array.IArray as Array
    import qualified Data.List as List
    import Control.Monad ((<$!>), guard)
    import qualified Data.Text.IO as TextIO
    import Data.Maybe (fromMaybe)
    import Control.Arrow ((&&&))
    
    parse :: Text.Text -> UArray (Int, Int) Bool
    parse t = let
        gridLines = init $ Text.lines t
        lineSize = maybe 0 pred $ Text.findIndex (== '\n') t
        lineCount = Text.count "\n" t - 2
      in Array.listArray ((0, 0), (lineCount, lineSize)) $ List.concatMap (fmap (== '@') . Text.unpack) gridLines
    
    neighbors8 :: (Int, Int) -> [(Int, Int)]
    neighbors8 p@(x, y) = do
      x' <- [pred x .. succ x]
      y' <- [pred y .. succ y]
      let p' = (x', y')
      guard (p /= p')
      pure p'
    
    main :: IO ()
    main = do
      grid <- parse <$!> TextIO.getContents
      print $ part1 grid
      print $ part2 grid
    
    part2 :: UArray (Int, Int) Bool -> Int
    part2 grid = case accessiblePositions grid of
      [] -> 0
      xs -> List.length xs + part2 (grid Array.// fmap (id &&& const False) xs)
    
    part1 :: UArray (Int, Int) Bool -> Int
    part1 = List.length . accessiblePositions
    
    accessiblePositions :: UArray (Int, Int) Bool -> [(Int, Int)]
    accessiblePositions grid = let
         lookupPosition = fromMaybe False . (grid Array.!?)
         positions = Array.indices grid
         paperRollPositions = List.filter lookupPosition positions
         isPositionAccessible = (< 4) . List.length . List.filter lookupPosition . neighbors8
       in List.filter isPositionAccessible paperRollPositions