Day 3: Lobby

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
    English
    arrow-up
    2
    ·
    1 month ago

    Futhark

    I am on my way to re-do all previous days in Futhark and complete the Rest of AoC, hopefully.

    def hole: u8 = 0
    def zipIndices 'a (xs: []a): [](i64, a) = zip (indices xs) xs
    def foldMin (xs: []u8): (i64, u8) = 
      let indexedXs = tail (zipIndices xs) in
      let start = (0, head xs) in
      foldl (\ (ci, cv) (ni, nv) -> if nv > cv then (ni, nv) else (ci, cv)) start indexedXs
    
    def slice 'a (xs: []a) (start: i64) (end: i64) = drop start (take end xs)
    
    def pickBattery (bank: []u8) (reserved: i64): (i64, u8) = 
      let batteries = slice bank 0 (length bank - reserved) in
      foldMin batteries
    
    def pickNBatteries (n: i8) (banks: []u8): u64 =
      let (_, result) =
        loop (batteries, sum) = (banks, 0)
        for i in reverse (0...n-1)
        do
          let (offset, battery) = pickBattery batteries (i64.i8 i) in
          (drop (offset + 1) batteries, sum * 10 + u64.u8 battery)
      in result
    
    def part1 (banks: [][]u8): u64 = reduce (+) 0 (map (pickNBatteries 2) banks)
    
    def part2 (banks: [][]u8): u64 = reduce (+) 0 (map (pickNBatteries 12) banks)
    
    def main (banks: [][]u8) = (part1 banks, part2 banks)
    
    Script to Generate input for Futhark
    {-# OPTIONS_GHC -Wall #-}
    {-# LANGUAGE OverloadedStrings #-}
    import qualified Data.Text.IO as TextIO
    import Control.Monad ((<$!>))
    import qualified Data.Array.Unboxed as Array
    import qualified Data.Text as Text
    import qualified Data.Char as Char
    import Data.Array.Unboxed (UArray)
    import qualified Data.List as List
    import qualified Data.ByteString as ByteString
    import Data.Word (byteSwap64, Word64)
    import GHC.ByteOrder (ByteOrder(..), targetByteOrder)
    import qualified Data.Bits as Bits
    
    parse :: Text.Text -> UArray (Int, Int) Int
    parse t = let
        banks = init $ Text.lines t
        bankSize = maybe 0 pred $ Text.findIndex (== '\n') t
        bankCount = Text.count "\n" t - 2
      in Array.listArray ((0, 0), (bankCount, bankSize)) $ List.concatMap (fmap Char.digitToInt . Text.unpack) banks
    
    rowsOf :: UArray (Int, Int) Int -> Int
    rowsOf = fst . snd . Array.bounds
    
    colsOf :: UArray (Int, Int) Int -> Int
    colsOf = snd . snd . Array.bounds
    
    byteStringLeWord64 :: Word64 -> ByteString.ByteString
    byteStringLeWord64 word = let
        leWord = case targetByteOrder of
          BigEndian -> byteSwap64 word
          LittleEndian -> word
      in ByteString.pack . map (fromIntegral . (leWord `Bits.shiftR`)) $ [0,8..56]
    
    main :: IO ()
    main = do
      batteryBanks <- parse <$!> TextIO.getContents
      putChar 'b'
      ByteString.putStr (ByteString.singleton 2) -- version
      ByteString.putStr (ByteString.singleton 2) -- dimensions
      TextIO.putStr "  u8" -- type
      ByteString.putStr (byteStringLeWord64 . fromIntegral . succ . rowsOf $ batteryBanks) -- outer dim
      ByteString.putStr (byteStringLeWord64 . fromIntegral . succ . colsOf $ batteryBanks) -- inner dim
      ByteString.putStr . ByteString.pack . fmap fromIntegral . Array.elems $ batteryBanks -- elements