This is part 2 of Day 4 of 2024's AoC: The problem is as follows:
It's an X-MAS puzzle in which you're supposed to find two MAS in the shape of an X. One way to achieve that is like this:
M.S
.A.
M.S
Irrelevant characters have again been replaced with . in the above diagram. Within the X, each MAS can be written forwards or backwards. Here's the same example from before, but this time all of the X-MASes have been kept instead:
.M.S......
..A..MSMS.
.M.S.MAA..
..A.ASMSM.
.M.S.M....
..........
S.S.S.S.S.
.A.A.A.A..
M.M.M.M.M.
..........
In this example, an X-MAS appears 9 times. The actual puzzle text is far larger, here's the first two lines for example:
SXMSMMXMASMSSSSXAMXMXAMXXAAXMAMSAMMXMAMXSAMXMXMMMMSMMXMXMASMMSMMSSSMAXXMSMSSXMASMXSSSXSMMSSSSSXMASXSAMXSMMSSMXXXXXMASXMXMSSSMMSSMSSSMMMMSSXM
SAMAMSMSMSXAAMAAXMSXMSSSXSXMSMMSASASXSMSMSSMSSMXAAMXMASXSAAMAXASAXMASXSASMASMMSMMAMXSAAXAXMAAAASAMAXAXASAAAAMMSMMSMMMASASAMXSAAAAMASMAASMMAS
There's 139 lines more. Here's a link to the source code and puzzle input, both large and small. The code works and I got the correct answer for the second part of the puzzle. Clearly I'm a beginner, I'm just getting on to typeclasses, but I'd like to know:
Firstly many reviews I read here and there say don't use indices (because it's vaguely imperative), but this seems to be an indices type of problem. The devil is in the detail, exact matches and accurate positioning of sub strings ie 'MAS' & 'SAM' are important. Thus am I solving this problem in the 'right way' and if not, what's a better way to solve it ?
Am I going over board on comments, function names etc ?
Any other style or function comments gratefully received.
I think function genSearchObjs is wrong (it works however). It's type return is wrong should I be using Maybe or similar type ?
I've included a step by step breakdown of what various variables are storing and what functions are returning for the small XMAS puzzle example posted above at the end of the code.
EDIT The code does compile and run using GHCi, version 9.4.8 I haven't tried it on other versions.
Here's the AoCTools Module
module AoCTools where
import Data.List (isPrefixOf)
count :: Eq a => a -> [a] -> Int
count x = length . filter (==x)
getLengthFromListElement :: [String] -> Int
getLengthFromListElement [] = 0
getLengthFromListElement (x:xs) = length x
countStr :: String -> String -> Int
countStr _ [] = 0
countStr sub str
| sub `isPrefixOf` str = 1 + countStr sub (drop (length sub) str)
| otherwise = countStr sub (tail str)
-- Given a list of lists, returns the first eleement of each list
firstElements :: [[a]] -> [a]
firstElements = map head
addToList :: Int -> [Int] -> [Int]
addToList x l = map (+x) l
The main code:
{-# LANGUAGE ParallelListComp #-}
{-# LANGUAGE FlexibleInstances #-}
module Csearch where
{- AoC Day 4 -}
import Data.List (findIndex)
import AoCTools
-- Represents the co-ordinates of each square of the puzzle, with 0,0 being top
-- left and co-ordinates getting larger moving to the right and down.
data Co_ords = Co_ords { col :: Int,
row :: Int
} deriving Eq
-- Am using a tilde here (~) because in the ouput there are commas everywhere,
-- and the tilde makes the co-ordinates standout and easier to read
instance Show Co_ords where
show (Co_ords col row) = show col ++ "~" ++ show row
-- Represents the co-ordinates of a square, the letter in it and the parent
-- string the letter is in. The parent strings are actually the diagonals on the
-- puzzle square, detailed later..I've named them Serach Obj(ects) because
-- they're being serached through to find combinations of letters within larger
-- strings, either MAS or SAM. This program could possibly exist without them
-- but it made debugging much easier.
data SearchObj = SearchObj { letter :: Char,
co_ords :: Co_ords,
parent_str :: String
} deriving Eq
-- Again slightly weird notation in the 'display strings'. This to try and keep
-- it short and clear when displaying many Search Objects
instance Show SearchObj where
show (SearchObj letter co_ords parent_str) = [letter] ++ "-" ++ show(co_ords) ++ ",$-" ++ parent_str ++ " "
-- Given a square generate a list of co-ords that represent a diagonal eg a 5 by
-- 5 square, starting at 0,0 at the top left (and going to, in this case, 4,4 at
-- the bottom) would return [(0, 0) (1, 1) (2, 2) (3, 3) (4, 4)] if direction is
-- positive. If direction is negative the diagonals go in the opposite way
generateADiagFrom :: Int -> Int -> Int -> Int -> [Co_ords]
generateADiagFrom start_col start_row size direction =
[ Co_ords x y | i <- [0..lmt], let x = col + (i * d), x <= lmt, x >= 0, let y = row + i, y >= 0, y <= lmt]
where
-- so d is either +1 or -1. Maybe I should have used a Bool or something
-- but direction in inherently mathmatical.
d = (direction `div` abs (direction))
col = start_col
row = start_row
lmt = size - 1
-- Given a square of square_size generates co-ords of all diagonals going top
-- left to bottom right The functions genDiagIndicesTopLefttoBottomRight &
-- genDiagIndicesTopRighttoBottomLeft were all one function. They were split in
-- order to do part 2 of the puzzle. If you imagine a square cut in half across
-- the diagonal, the topHalf is the triangle escribed by top left, top right,
-- bottom right (and back) to top left. bottomHalf is the other half.
genDiagIndicesTopLefttoBottomRight :: Int -> [[Co_ords]]
genDiagIndicesTopLefttoBottomRight square_size = topHalf ++ bottomHalf
where
positive = 1
limit = square_size - 1
topHalf = [(generateADiagFrom x 0 square_size positive) | x <- [0..limit] ]
bottomHalf = [(generateADiagFrom 0 y square_size positive) | y <- [1..limit] ]
-- Given a square of square_size generates co-ords of all diagonals going top
-- left to bottom right
genDiagIndicesTopRighttoBottomLeft :: Int -> [[Co_ords]]
genDiagIndicesTopRighttoBottomLeft square_size = topHalf ++ bottomHalf
where
negative = -1
limit = square_size - 1
topHalf =
[(generateADiagFrom (limit - x) 0 square_size negative) | x <- [0..limit] ]
bottomHalf =
[(generateADiagFrom limit (limit - y) square_size negative) | y <- [1..(limit - 1)] ]
-- Given a string and a list of co-ordinates create a list of SearchObj from
-- them. With hindsight could possibly use a map ?
genSearchObjs :: String -> [Co_ords] -> [SearchObj]
genSearchObjs diag_str [] = []
genSearchObjs diag_str coordsAr =
if length diag_str /= length coordsAr then error ("Help: " ++ diag_str ++ show(coordsAr) ++ " end of error genSearchObjs")
else [SearchObj (diag_str !! i) (coordsAr !! i) diag_str | i <- [0 .. (length diag_str - 1)] ]
-- Remaps the string to a new set of Co_ords
co_ordsToString :: [String] -> [Co_ords] -> String
co_ordsToString stringsBeforeReorganising [] = []
co_ordsToString stringsBeforeReorganising (x:xs) =
[char] ++ co_ordsToString stringsBeforeReorganising xs
where
Co_ords a b = x
char = (stringsBeforeReorganising !! b) !! a
-- Given a lists of strings re-organise each character based on the list of
-- Co_ords. See notes at beginning of main ()
genStringsFromCoords :: [String] -> [[Co_ords]] -> [String]
genStringsFromCoords stringsBeforeReorganising co_ords =
map (co_ordsToString stringsBeforeReorganising) co_ords
-- Given a list of lists of Search Objcts (SearchObj) returns a list of all the parent
-- strings (parent_str) of those Search Objects
getStringsFromListsOfLists :: [[SearchObj]] -> [String]
getStringsFromListsOfLists = map parent_str . firstElements
-- Given a string returns the indices of the letter 'A' in that string
-- eg indicesOf_A "MSAMMMMXAM" returns [2,8]
indicesOf_A :: String -> [Int]
-- indices 1 to length -2 because will be testing for SM above and below and
-- it's easier to sort here
indicesOf_A str = [ i | i <- [1..((length str) - 2)], str !! i == 'A']
-- I think (though I maybe wrong) I have to use indices here because of the
-- shape of the puzzle and solution the letters have to be in a specific
-- positions in 2 dimensions..
-- Given a string the index of the letter A which is part of either SAM or MAS
-- eg indicesOfSAM_or_MAS "MSAMMMMXAM" returns 2
indicesOfSAM_or_MAS :: String -> [Int]
indicesOfSAM_or_MAS str = [ i | i <- indicesOf_A str, check i]
where
check idx = (str !! (idx - 1) == 'S' && str !! (idx + 1) == 'M') || (str !! (idx - 1) == 'M' && str !! (idx + 1) == 'S')
-- Given a list of column values (Co_ord) return the corresponding column and
-- row values
getRowAndColumnFromJustColumn :: [Int] -> [Co_ords]-> [Co_ords]
getRowAndColumnFromJustColumn cols = filter (\c -> col c `elem` cols)
-- Function to find the index of a Co_ords in the list, based on column value
findCoordIndex :: [Co_ords] -> [SearchObj] -> [Maybe Int]
findCoordIndex target searchObjs =
[findIndex (== t_elem) (map (\x -> co_ords x) searchObjs) | t_elem <-target]
-- Function to filter out Just values and get the corresponding integers
type Input = [([Maybe Int], Int)]
extractJustValues :: Input -> [(Int, Int)]
extractJustValues = concatMap extractFromTuple
where
-- Extract the value and pair it with n if it's Just
extractFromTuple (xs, n) = [(val, n) | Just val <- xs]
-- Given a pair of indices (of the letter 'A') return True if that 'A' is in the
-- middle of "SAM" or "MAS"
isThereA_SAM_OrMAS_AtIndex :: (Int,Int) -> [[SearchObj]] -> Bool
isThereA_SAM_OrMAS_AtIndex (col,row) searchObjList
| col - 1 < 0 = False
| col + 1 > (length (searchObjList!!row)) - 1 = False
| otherwise = sam || mas
where
sOL = searchObjList
sam =
letter ((sOL!!row)!!(col - 1)) =='S' && letter ((sOL!!row)!!(col + 1)) == 'M'
mas =
letter ((sOL!!row)!!(col - 1)) =='M' && letter ((sOL!!row)!!(col + 1)) == 'S'
main :: IO ()
main = do
-- contents <- readFile "04/puzzle_input.txt" -- The man puzzle input
contents <- readFile "04/small_test.txt" -- This is the small test file
let l = getLengthFromListElement (lines contents)
-- Take the input and instead of spitting it into lines and columns am
-- rearranging the square into a new square of diagonals, arranging the
-- square into lines of diagonals top left to bottom right and top right to
-- bottom left. eg: say the input was this
-- A B C D E
-- F G H I J
-- K L M N O
-- P Q R S T
-- U V W X Y
-- then it'll be re-arranged into two configuarations:
-- E and A
-- D J B F
-- C I O C G K
-- B H N T D H L P
-- A G M S Y E I M Q U
-- F L R X J N R V
-- K Q W O S W
-- P V T X
-- U Y
-- And the program then looks for strings in those arrangements. Obviously
-- the puzzle file is much bigger (141 x 141) and filled with X,M,A,S. The
-- small puzzle file is only 10 x 10.
-- Imagining that the square starts at 0,0 and goes down to 141,141 (and
-- 141,0 to 0,141) the program generates all the coordinates of the
-- diagonals (or 10-1 ,10-1 & 10-1,0/0,10-1) 10 - 1 because all those the
-- puzzle is 10 x 10 the indices will be 0-9 if we're solving the small
-- puzzle.
let co_ordsTopLefttoBottomRight = genDiagIndicesTopLefttoBottomRight l
co_ordsTopRightToBottomLeft = genDiagIndicesTopRighttoBottomLeft l
-- Get the text from the file and turn it into a list of lines of text.
puzzleLines = lines contents
-- Combining the diagonal co-ordinates (both ways) with the puzzle
-- strings to get a list of strings that are made up from all the
-- diagonals (as we're looking for Xs).
diagonalStrsTopLeftToBottomRight =
genStringsFromCoords puzzleLines co_ordsTopLefttoBottomRight
diagonalStrsTopRightToBottomLeft =
genStringsFromCoords puzzleLines co_ordsTopRightToBottomLeft
-- The length of dTopLeft2BottomRight and co_ordsTopLefttoBottomRight
-- should always be the same as they were generated from the same
-- pattern; which is each set of Co_ords matched with the letter in the
-- diagonal and the DIAGONAL parent_string.
first_SearchObjs =
zipWith genSearchObjs diagonalStrsTopLeftToBottomRight co_ordsTopLefttoBottomRight
-- Which is each set of Co_ords matched with the letter at those co-ords
-- and the DIAGONAL (but diagonals going top right down to bottom left)
-- and the parent_string the letter is in.
second_SearchObjs =
zipWith genSearchObjs diagonalStrsTopRightToBottomLeft co_ordsTopRightToBottomLeft
-- That is the location of the letter A in the lines of the puzzle
-- (which are strings).
locationOfAsInStrings =
map indicesOfSAM_or_MAS (getStringsFromListsOfLists $ first_SearchObjs)
-- The first column co_ord(inate) will be how much each column value has
-- to be shifted (to the right) to get the actual column co_ord value.
-- This combined with the row index will reveal the co_ordinates of the
-- A's.
perRowColumnAdjustment = map (col . head) co_ordsTopLefttoBottomRight
-- Get the actual column value.
adjustedColumnCoordinate =
zipWith addToList perRowColumnAdjustment locationOfAsInStrings
-- Get the Co_ords from the column values.
co_ordsWithPotentialSAMMAS =
zipWith getRowAndColumnFromJustColumn adjustedColumnCoordinate co_ordsTopLefttoBottomRight
-- Get the indices of the second seachObjs from the co-ordinates.
sSOs = second_SearchObjs
cPotSAM = co_ordsWithPotentialSAMMAS
lmt = (length sSOs) - 1
indicesOfSearchObjects =
[ [((findCoordIndex cs (sSOs!!i)) ,i) | i <- [0..lmt] ] | cs <- cPotSAM ]
-- Tidy up the output because it's a bit of a mess !
tidiedSearchObjIndices = concat $ map extractJustValues indicesOfSearchObjects
-- Given the indices of As in the second SearchObjects' list find out if
-- they're also the indices of "SAM" or "MAS" and if so return True.
let final_result = fmap (`isThereA_SAM_OrMAS_AtIndex` second_SearchObjs) tidiedSearchObjIndices
putStrLn("\nThere are " ++ show (count True final_result) ++ " X MASes !")
{- Notes
For the small puzzle test data, here are what some of the various variables are
at stages through the code which will hopefully help explain what's going on...
(With added spaces to make reading easier. There are NO SPACES in contents or
(line contents):[
"M M M S X X M A S M",
"M S A M X M S M S A",
"A M X S X M A A M M",
"M S A M A S M S M X",
"X M A S A M X A M M",
"X X A M M X X A M A",
"S M S M S A S X S S",
"S A X A M A S A A A",
"M A M M M X M M M M",
"M X M X A X M A S X"]
Co_ordinates start at top left 0,0 and finish at bottom right l,l. (l = (length
head lines contents) - 1)
co_ordsTopLefttoBottomRight: (Column ~ Row, I've used the tilde to indentify the
Co_ord type, tere are a lot of commas in the output)
[[0~0,1~1,2~2,3~3,4~4,5~5,6~6,7~7,8~8,9~9],
[1~0,2~1,3~2,4~3,5~4,6~5,7~6,8~7,9~8],
[2~0,3~1,4~2,5~3,6~4,7~5,8~6,9~7],
[3~0,4~1,5~2,6~3,7~4,8~5,9~6],
[4~0,5~1,6~2,7~3,8~4,9~5],
[5~0,6~1,7~2,8~3,9~4],
[6~0,7~1,8~2,9~3],
[7~0,8~1,9~2],
[8~0,9~1],
[9~0],
[0~1,1~2,2~3,3~4,4~5,5~6,6~7,7~8,8~9],
[0~2,1~3,2~4,3~5,4~6,5~7,6~8,7~9],
[0~3,1~4,2~5,3~6,4~7,5~8,6~9],
[0~4,1~5,2~6,3~7,4~8,5~9],
[0~5,1~6,2~7,3~8,4~9],
[0~6,1~7,2~8,3~9],
[0~7,1~8,2~9],
[0~8,1~9],
[0~9]]
There's also the Co-ords for the diagonals the other way,
co_ordsTopRightToBottomLeft. Which I've Not included for brevity
Given co_ordsTopLefttoBottomRight and the contents of the puzzle file (lines
contents) a new set of strings was created based on those co-ordinates. The
letter at 0~0 is M, at 1~1 is S, 2~2 is X ... 7~7 is A 8~8 is M and 9~9 is X The
letter at 1~0 is M, at 2~1 is A etc etc. Combining the co-ordinate set with the
origional strings gives this set of strings:
diagonalStrsTopLeftToBottomRight:
["MSXMAXSAMX","MASAMXXAM","MMXSXASA","SXMMAMS","XMASMA","XSAMM","MMMX","ASM","SA","M",
"MMASMASMS","ASAMSAMA","MMAMMXM","XXSAMX","XMXMA","SAMX","SAM","MX","M"]
And for the diagonals going the other way
diagonalStrsTopRightToBottomLeft:
["MSAMMMMXAM","SMASAMSAM","ASMASAMS","MMXMAXS","XXSAMX","XMXSX","SAMM","MSA","MM",
"M","MS","AMA","SAMM","ASAMX","MMXSXA","XMASAMX","MMAXAMMM","AMSXXSAMX"]
first_SearchObjs:
(Which is each set of Co_ords matched with the letter there and the DIAGONAL parent_string)
[
[M-0~0,$-MSXMAXSAMX ,S-1~1,$-MSXMAXSAMX ,X-2~2,$-MSXMAXSAMX ,M-3~3,$-MSXMAXSAMX ,A-4~4,$-MSXMAXSAMX ,X-5~5,$-MSXMAXSAMX
,S-6~6,$-MSXMAXSAMX ,A-7~7,$-MSXMAXSAMX ,M-8~8,$-MSXMAXSAMX ,X-9~9,$-MSXMAXSAMX ],
[M-1~0,$-MASAMXXAM ,A-2~1,$-MASAMXXAM ,S-3~2,$-MASAMXXAM ,A-4~3,$-MASAMXXAM ,M-5~4,$-MASAMXXAM ,X-6~5,$-MASAMXXAM,
X-7~6,$-MASAMXXAM ,A-8~7,$-MASAMXXAM ,M-9~8,$-MASAMXXAM ],
[M-2~0,$-MMXSXASA ,M-3~1,$-MMXSXASA ,X-4~2,$-MMXSXASA ,S-5~3,$-MMXSXASA ,X-6~4,$-MMXSXASA ,A-7~5,$-MMXSXASA
,S-8~6,$-MMXSXASA ,A-9~7,$-MMXSXASA ],
[S-3~0,$-SXMMAMS ,X-4~1,$-SXMMAMS ,M-5~2,$-SXMMAMS ,M-6~3,$-SXMMAMS ,A-7~4,$-SXMMAMS ,M-8~5,$-SXMMAMS ,S-9~6,$-SXMMAMS ],
[X-4~0,$-XMASMA ,M-5~1,$-XMASMA ,A-6~2,$-XMASMA ,S-7~3,$-XMASMA ,M-8~4,$-XMASMA ,A-9~5,$-XMASMA ],
[X-5~0,$-XSAMM ,S-6~1,$-XSAMM ,A-7~2,$-XSAMM ,M-8~3,$-XSAMM ,M-9~4,$-XSAMM ],
[M-6~0,$-MMMX ,M-7~1,$-MMMX ,M-8~2,$-MMMX ,X-9~3,$-MMMX ],
[A-7~0,$-ASM ,S-8~1,$-ASM ,M-9~2,$-ASM ],
[S-8~0,$-SA ,A-9~1,$-SA ],
[M-9~0,$-M ],
[M-0~1,$-MMASMASMS ,M-1~2,$-MMASMASMS ,A-2~3,$-MMASMASMS ,S-3~4,$-MMASMASMS ,M-4~5,$-MMASMASMS ,A-5~6,$-MMASMASMS ,
S-6~7,$-MMASMASMS ,M-7~8,$-MMASMASMS ,S-8~9,$-MMASMASMS ],
[A-0~2,$-ASAMSAMA ,S-1~3,$-ASAMSAMA ,A-2~4,$-ASAMSAMA ,M-3~5,$-ASAMSAMA ,S-4~6,$-ASAMSAMA ,A-5~7,$-ASAMSAMA ,
M-6~8,$-ASAMSAMA ,A-7~9,$-ASAMSAMA ],
[M-0~3,$-MMAMMXM ,M-1~4,$-MMAMMXM ,A-2~5,$-MMAMMXM ,M-3~6,$-MMAMMXM ,M-4~7,$-MMAMMXM ,X-5~8,$-MMAMMXM ,
M-6~9,$-MMAMMXM ],
[X-0~4,$-XXSAMX ,X-1~5,$-XXSAMX ,S-2~6,$-XXSAMX ,A-3~7,$-XXSAMX ,M-4~8,$-XXSAMX ,X-5~9,$-XXSAMX ],
[X-0~5,$-XMXMA ,M-1~6,$-XMXMA ,X-2~7,$-XMXMA ,M-3~8,$-XMXMA ,A-4~9,$-XMXMA ],
[S-0~6,$-SAMX ,A-1~7,$-SAMX ,M-2~8,$-SAMX ,X-3~9,$-SAMX ],
[S-0~7,$-SAM ,A-1~8,$-SAM ,M-2~9,$-SAM ],
[M-0~8,$-MX ,X-1~9,$-MX ],
[M-0~9,$-M ]]
and second_SearchObjs is all the Search Objects for the diagonals in the
opposite direction ie top right to bottom left
The we look for all the indices of the letter 'A's which is in either a SAM or
MAS which gives this list, which is in terms of the index of the paret string,
not the column number: (Check against first_SearchObjs!) locationOfAsInStrings:
[[7],[1,3],[],[],[2],[2],[],[],[],[],[2,5],[2,5],[],[3],[],[1],[1],[],[]]
To get the column number of the co_ord (of the letter A in SAM or MAS), have to
get the 'column offset' which is the first column number in each row of
SearchObjects: perRowColumnAdjustment: [0,1,2,3,4,5,6,7,8,9,0,0,0,0,0,0,0,0,0]
Add the corresponding perRowColumnAdjustment to the list of column to
locationOfAsInStrings to get the column co_ordinate of each SAM (or MAS)
adjustedColumnCoordinate:
[[7],[2,4],[],[],[6],[7],[],[],[],[],[2,5],[2,5],[],[3],[],[1],[1],[],[]]
In the first row of search Objects ie (index 0) the Co_ords with a column value
of 7 is 7~7. In the second row (Index 1) Co_ords with a column value of 2 & 4
are 2~1 & 4~3 etc This is what function getRowAndColumnFromJustColumn does,
which gives us this list of co-ordinates (of the letter 'A') that contain SAM or
MAS in all the diagonals going from top left to bottom right.
co_ordsWithPotentialSAMMAS:
[[7~7],[2~1,4~3],[],[],[6~2],[7~2],[],[],[],[],[2~3,5~6],[2~4,5~7],[],[3~7],[],[1~7],[1~8],[],[]]
Given these Co_ords, when then need to find the indices of the second_searchObjs
that those co-ords correspond with (then we can find out if they're in a SAM or
MAS) but first the convervesio into second_SearchObject indices:
Anything with a Just value in are the indices of the 'A's in the
second_SearchObjs. Eg ([N,Just3],2) => Indices 3~2. indicesOfSearchObjects:
[[([N],0),([N],1),([N],2),([N],3),([N],4),([N],5),([N],6),([N],7),([N],8),([N],9),([N],10),([N],11),([N],12),([Just2],13),
([N],14),([N],15),([N],16),([N],17)], [([N,N],0),([N,N],1),([N,Just3],2),([N,N],3),([N,N],4),([N,N],5),([Just1,N],6),
([N,N],7),([N,N],8),([N,N],9),([N,N],10),([N,N],11),([N,N],12),([N,N],13),([N,N],14),([N,N],15),([N,N],16),([N,N],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),([],14),
([],15),([],16),([],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),([],14),
([],15),([],16),([],17)],
[([N],0),([Just2],1),([N],2),([N],3),([N],4),([N],5),([N],6),([N],7),([N],8),([N],9),([N],10),([N],11),([N],12),
([N],13),([N],14),([N],15),([N],16),([N],17)],
[([Just2],0),([N],1),([N],2),([N],3),([N],4),([N],5),([N],6),([N],7),([N],8),([N],9),([N],10),([N],11),([N],12),
([N],13),([N],14),([N],15),([N],16),([N],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),([],14),
([],15),([],16),([],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),([],14),
([],15),([],16),([],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),([],14),
([],15),([],16),([],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),([],14),
([],15),([],16),([],17)],
[([N,N],0),([N,N],1),([N,N],2),([N,N],3),([Just3,N],4),([N,N],5),([N,N],6),([N,N],7),([N,N],8),([N,N],9),([N,N],10),
([N,N],11),([N,N],12),([N,N],13),([N,N],14),([N,N],15),([N,Just4],16),([N,N],17)],
[([N,N],0),([N,N],1),([N,N],2),([Just4,N],3),([N,N],4),([N,N],5),([N,N],6),([N,N],7),([N,N],8),([N,N],9),([N,N],10),
([N,N],11),([N,N],12),([N,N],13),([N,N],14),([N,Just4],15),([N,N],16),([N,N],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),
([],14),([],15),([],16),([],17)],
[([N],0),([N],1),([N],2),([N],3),([N],4),([N],5),([N],6),([N],7),([N],8),([N],9),([N],10),([N],11),([N],12),
([N],13),([N],14),([N],15),([N],16),([Just6],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),
([],14),([],15),([],16),([],17)],
[([N],0),([Just7],1),([N],2),([N],3),([N],4),([N],5),([N],6),([N],7),([N],8),([N],9),([N],10),([N],11),([N],12),
([N],13),([N],14),([N],15),([N],16),([N],17)],
[([Just8],0),([N],1),([N],2),([N],3),([N],4),([N],5),([N],6),([N],7),([N],8),([N],9),([N],10),([N],11),([N],12),
([N],13),([N],14),([N],15),([N],16),([N],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),
([],14),([],15),([],16),([],17)],
[([],0),([],1),([],2),([],3),([],4),([],5),([],6),([],7),([],8),([],9),([],10),([],11),([],12),([],13),([],14),
([],15),([],16),([],17)]]
tidiedSearchObjIndices:
[(2,13),(3,2),(1,6),(2,1),(2,0),(3,4),(4,16),(4,3),(4,15),(6,17),(7,1),(8,0)]
All that remains is using those co-ordinates to see if there are SAM or MAS at
those co-ordinates in the other diagonals going from top right to bottom left:
-}
2 Answers 2
Sorry, but your solution seems like overly complicated. Naive but in Haskell style might look like this:
import Data.List (transpose)
main :: IO ()
main = do
lns <- lines <$> readFile "puzzle_input.txt"
print
$ length
$ filter isXMAS
$ concatMap (scanBy3 . transpose)
$ scanBy3 lns
isXMAS :: [[Char]] -> Bool
isXMAS [[a, _, b], [_, x, _], [c, _, d]]
= ([a, x, d] == "MAS" || [a, x, d] == "SAM")
&& ([b, x, c] == "MAS" || [b, x, c] == "SAM")
isXMAS _ = error "Unexpected shape"
scanBy3 :: [a] -> [[a]]
scanBy3 (x:xs@(y:z:_)) = [x,y,z] : scanBy3 xs
scanBy3 _ = []
Random nitpicks to your code.
- There is no need to make helper function out of
map head
andmap (+x)
. They are concise and recognizable enough without additional comment or explanation. Moreover, as a rule of thumb, rare function should be likefoo = map <expr>
. Havingfoo = <expr>
allows more ways to combine. - The same applies to
filter
: it is better to haveisColumnOf = elem . col
and instead ofgetRowAndColumnFromJustColumn cols = filter ...
[SearchObj (diag_str !! i) (coordsAr !! i) diag_str | i <- [0 .. (length diag_str - 1)] ]
is equivalent tozipWith (\a b -> SearchObj a b diag_str) diag_str coordsAr
[char] ++ <expr>
is equvalent tochar : <expr>
co_ordsToString
can be rewritten asco_ordsToString strBefore = map (\Co_ords a b -> (strBefore !! a) !! b)
- sometimes comprehensions are a great tool, but try not to overuse them:
indicesOf_A str = [ i | i <- [1..((length str) - 2)], str !! i == 'A']
is the same asmap fst . filter ((== 'A').snd) . zip [1..]
but less efficient becausestr !! i
is O(n).
-
1\$\begingroup\$ How did you get the much better solution (> 200 lines to 20)? Was it understanding the problem better and coming to an obvious solution? Or re-working mine (very much less likely) to be much more efficient. I'd like to write code like yours, not mine so am wondering if you have any insight to your process you could add? \$\endgroup\$Lozminda– Lozminda2024年12月21日 21:01:17 +00:00Commented Dec 21, 2024 at 21:01
-
1\$\begingroup\$ @Lozminda, sorry for the late response. I always try to start with the most obvious and naive solution. I could be inefficient, but you can run it on problems of smaller sizes to get insights on how to optimize. And you can use it later to test optimized code. In this particular case the simplest solution was enough. \$\endgroup\$max taldykin– max taldykin2024年12月24日 21:09:19 +00:00Commented Dec 24, 2024 at 21:09
I let myself get nerd-sniped by this quite badly. If you feel like learning comonads, this is a pretty normal example; if you've got enough else to worry about then my solution won't be useful to you.
Most of the complexity is in deciding how duplicate
should handle ragged arrays. This is technically out-of-scope for this problem, so any choice of behavior would be fine.
It's a little bit golfed, for which I apologize.
import Control.Comonad
import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Maybe (fromMaybe, mapMaybe)
newtype Grid a = Grid{raw :: NonEmpty (NonEmpty a)}
deriving (Foldable, Read, Show, Functor, Traversable)
instance Comonad Grid where
extract = NE.head . NE.head . raw
duplicate g = Grid $ (g :| headtail) :| tailtail
where tailtail = maybe [] NE.toList $ (raw . duplicate . Grid <$>) . maybeTail $ raw g
headtail = maybe [] NE.toList $
(NE.head . raw . duplicate . Grid <$>) . right $ raw g
maybeTail = snd . NE.uncons
right g = (:| mapMaybe maybeTail (NE.tail g)) <$> (maybeTail . NE.head $ g)
isXMas :: Grid Char -> Bool
isXMas (Grid ( (c11 :| (c12 : c13 : _))
:| ( (c21 :| (c22 : c23 : _))
:(c31 :| (c32 : c33 : _)) : _) )) = isMS [c11,c22,c33] && isMS [c31,c22,c13]
where isMS = (`elem` ["MAS", "SAM"])
isXMas _ = False
countXMass :: Grid Char -> Int
countXMass g = sum $ fromEnum <$> extend isXMas g
loadString :: String -> Grid Char
loadString = Grid . (NE.fromList <$>) . NE.fromList . lines
Explore related questions
See similar questions with these tags.
genSearchObjs()
toMaybe
?" But this "function genSearchObjs is wrong (it works however). It's type return is wrong should I be using Maybe or similar type?" can be interpreted as a request for code rewriting (not reviewing the current implementation). \$\endgroup\$isXMAS
so I'm assuming my question was understood if only indirectly, as request for a review rather than a correction. I appreciate I'm using direct language and it's true 'science is done in the passive voice' though that's changing (perhaps). \$\endgroup\$genSearchObjs()
be improved by switching its return type toMaybe
?" (is a question about a possibility of redesign; and now that's a passive voice BTW) and "functiongenSearchObjs
is wrong, its type return is wrong" (it states with *certainty that the return type is "wrong", which creates a lot of room for misinterpretation, because "wrong" means not correct or truthful, erroneous). This ambiguous wording is what caused the question closure in the first place. \$\endgroup\$