From 0dbe7d9a79f7089f499acc87c11380778629b172 Mon Sep 17 00:00:00 2001
From: Felix Valentini <felixvalentini@Felixs-MBP.fritz.box>
Date: Tue, 6 Dec 2022 00:21:49 +0100
Subject: [PATCH] solved part one of day 5

---
 5/solve.hs | 49 ++++++++++++++++++++++++++++++++++++++-----------
 1 file changed, 38 insertions(+), 11 deletions(-)

diff --git a/5/solve.hs b/5/solve.hs
index 43ae373..896a320 100644
--- a/5/solve.hs
+++ b/5/solve.hs
@@ -1,19 +1,25 @@
+{-# LANGUAGE MultiWayIf #-}
+
 import Data.Char
 import Data.List
 
 -- input depth: 8
 -- sample depth: 3
-parseStack :: Int -> IO [(Int, String)]
-parseStack depth = (zip [1 .. ] <$> map (filter (/= ' ')))
+parseStack :: Int -> IO [String]
+parseStack depth = map (filter (/= ' '))
     . filter (any isUpper) . (transpose <$> take depth) . lines
     <$> readFile "./input.txt"
 
+-- newer copy shit from the internet fucked up my parser!!
 numbers :: String -> [Int]
 numbers [] = []
 numbers (l:ls) = if ord l >= 48 && ord l <= 57
     then (ord l - 48) : numbers ls
     else numbers ls
 
+numbers' :: String -> [Int]
+numbers' = map (read :: String -> Int) . words . filter (not . isAlpha)
+
 -- designed for lists == length 3
 tuplify3 :: [a] -> (a, a, a)
 tuplify3 (x1:x2:x3:_) = (x1, x2, x3)
@@ -23,20 +29,41 @@ dropFirst 0 xs = xs
 dropFirst n (_:xs) = dropFirst (n-1) xs
 
 -- input depth: 10
--- input depth: 5
+-- sample depth: 5
 parseMoves :: Int -> IO [(Int, Int, Int)]
 parseMoves depth = readFile "./input.txt"
-    >>= (return . map (tuplify3 . numbers)) . (dropFirst depth <$> lines)
+    >>= (return . map (adjustToListIndices . tuplify3 . numbers')) . (dropFirst depth <$> lines)
+
+adjustToListIndices :: (Int, Int, Int) -> (Int, Int, Int)
+adjustToListIndices (times, from, to) = (times, (from - 1), (to - 1))
+
+move :: Int -> Int -> [String] -> [String]
+move from to l =  map (\x -> if
+                           | x == from -> (tail (l !! from))
+                           | x == to   -> prepend ((l !! from) !! 0) (l !! to)
+                           | otherwise -> l !! x) [0..(length l) - 1]
 
+nMove :: (Int, Int, Int) -> [String] -> [String]
+nMove (1, from, to) l = move from to l
+nMove (times, from, to) l = nMove (times - 1, from, to) $ move from to l
 
-----------------------------------------------------------------------------------------------------
+moves :: [(Int, Int, Int)] -> [String] -> [String]
+moves [x] l = nMove x l
+moves (x:xs) l = moves xs (nMove x l)
 
--- must be in range of the stack, otherwise it throws an exception
-lookupStack :: Int -> [(Int, String)]-> String
-lookupStack n l = snd $ head $ filter (\(k, _) -> k == n) l
+solution1 :: [String] -> String
+solution1 = map (head)
 
-move :: (Int, Int, Int) -> [(Int, String)] -> String
-move (times, from, to) = undefined
+prepend :: a -> [a] -> [a]
+prepend a xs = a : xs
+
+fib :: Int -> Int
+fib 0 = 1
+fib n = n * (n - 1)
+
+-- To solve I need a foldr
+-- e.x. nMove (1, 0, 1) (nMove (2, 1, 0) (nMove (3, 0, 2) (nMove (1, 1, 0) stack)))
 
 main :: IO ()
-main = undefined
+main = pure (moves) <*> parseMoves 10 <*> parseStack 8 >>= print
+
-- 
GitLab