My yearly advent-of-code solutions
at main 5.4 kB view raw
1module day_08_utils 2 implicit none 3 type node 4 character :: c 5 integer, allocatable :: x(:), y(:) 6 end type node 7contains 8 subroutine append_to_integer_array(arr, val) 9 implicit none 10 integer, allocatable, intent(inout) :: arr(:) 11 integer, intent(in) :: val 12 integer, allocatable :: temp(:) 13 if(.not. allocated(arr)) then 14 ERROR STOP 'Array not allocated' 15 end if 16 allocate(temp(size(arr) + 1)) 17 temp(1:size(arr)) = arr 18 temp(size(arr) + 1) = val 19 call move_alloc(temp, arr) 20 end subroutine append_to_integer_array 21 22 subroutine add_node(nodes, c, x, y) 23 type(node), allocatable, intent(inout) :: nodes(:) 24 type(node), allocatable :: temp(:) 25 character, intent(in) :: c 26 integer, intent(in) :: x, y 27 integer :: i 28 do i = 1, size(nodes) 29 if (nodes(i)%c == c) then 30 if(.not. allocated(nodes(i)%x)) then 31 allocate(nodes(i)%x(1)) 32 nodes(i)%x(1) = x 33 else 34 call append_to_integer_array(nodes(i)%x, x) 35 end if 36 if(.not. allocated(nodes(i)%y)) then 37 allocate(nodes(i)%y(1)) 38 nodes(i)%y(1) = y 39 else 40 call append_to_integer_array(nodes(i)%y, y) 41 end if 42 return 43 end if 44 end do 45 allocate(temp(size(nodes) + 1)) 46 temp(1:size(nodes)) = nodes 47 allocate(temp(size(nodes) + 1)%x(1)) 48 allocate(temp(size(nodes) + 1)%y(1)) 49 temp(size(nodes) + 1)%c = c 50 temp(size(nodes) + 1)%x(1) = x 51 temp(size(nodes) + 1)%y(1) = y 52 call move_alloc(temp, nodes) 53 end subroutine add_node 54end module day_08_utils 55 56program day_08 57 use day_08_utils 58 implicit none 59 character(len=50) :: lines(50) 60 integer :: io, i, j, k, l, score, xdist, ydist, next_x, next_y 61 integer, allocatable :: anti_x(:), anti_y(:) 62 type(node), allocatable :: nodes(:) 63 logical :: found 64 65 open(newunit=io, file='day_08_input.txt', status='old', action='read') 66 read(io, '(A)') lines 67 score = 0 68 do i = 1, 50 69 do j = 1, 50 70 if(lines(i)(j:j) /= '.') then 71 if(.not. allocated(nodes)) then 72 allocate(nodes(1)) 73 nodes(1)%c = lines(i)(j:j) 74 allocate(nodes(1)%x(1)) 75 allocate(nodes(1)%y(1)) 76 nodes(1)%x(1) = j 77 nodes(1)%y(1) = i 78 else 79 call add_node(nodes, lines(i)(j:j), j, i) 80 end if 81 end if 82 end do 83 end do 84 do i = 1, size(nodes) 85 do j = 1, size(nodes(i)%x) 86 if(.not. allocated(anti_x)) then 87 allocate(anti_x(1)) 88 anti_x(1) = nodes(i)%x(j) 89 allocate(anti_y(1)) 90 anti_y(1) = nodes(i)%y(j) 91 score = score + 1 92 else 93 found = .false. 94 do k = 1, size(anti_x) 95 if(anti_x(k) == nodes(i)%x(j) .and. anti_y(k) == nodes(i)%y(j)) then 96 found = .true. 97 exit 98 end if 99 end do 100 if(.not. found) then 101 call append_to_integer_array(anti_x, nodes(i)%x(j)) 102 call append_to_integer_array(anti_y, nodes(i)%y(j)) 103 104 score = score + 1 105 end if 106 end if 107 do l = 1, size(nodes(i)%x) 108 if(nodes(i)%x(j) == nodes(i)%x(l) .and. nodes(i)%y(j) == nodes(i)%y(l)) cycle ! don't compare same values 109 xdist = nodes(i)%x(j) - nodes(i)%x(l) 110 ydist = nodes(i)%y(j) - nodes(i)%y(l) 111 next_x = nodes(i)%x(j) + xdist 112 next_y = nodes(i)%y(j) + ydist 113 do 114 if(next_x> 0 .and. next_x <= 50 .and. & 115 next_y > 0 .and. next_y <= 50) then 116 found = .false. 117 do k = 1, size(anti_x) 118 if(anti_x(k) == next_x .and. anti_y(k) == next_y) then 119 found = .true. 120 exit 121 end if 122 end do 123 if(.not. found) then 124 call append_to_integer_array(anti_x, next_x) 125 call append_to_integer_array(anti_y, next_y) 126 127 score = score + 1 128 end if 129 next_x = next_x + xdist 130 next_y = next_y + ydist 131 else 132 exit 133 end if 134 end do 135 next_x = nodes(i)%x(l) - xdist 136 next_y = nodes(i)%y(l) - ydist 137 do 138 if(next_x > 0 .and. next_x <= 50 .and. & 139 next_y > 0 .and. next_y <= 50) then 140 found = .false. 141 do k = 1, size(anti_x) 142 if(anti_x(k) == next_x .and. anti_y(k) == next_y) then 143 found = .true. 144 exit 145 end if 146 end do 147 if(.not. found) then 148 call append_to_integer_array(anti_x, next_x) 149 call append_to_integer_array(anti_y, next_y) 150 151 score = score + 1 152 end if 153 next_x = next_x - xdist 154 next_y = next_y - ydist 155 156 else 157 exit 158 end if 159 end do 160 end do 161 end do 162 end do 163 print*, "Total : ", score 164end program day_08