problem_25 Program

Uses

  • program~~problem_25~~UsesGraph program~problem_25 problem_25 module~aoc_utilities aoc_utilities program~problem_25->module~aoc_utilities module~dag_module dag_module program~problem_25->module~dag_module iso_fortran_env iso_fortran_env module~aoc_utilities->iso_fortran_env

Calls

program~~problem_25~~CallsGraph program~problem_25 problem_25 interface~split aoc_utilities::split program~problem_25->interface~split interface~unique~2 aoc_utilities::unique program~problem_25->interface~unique~2 proc~clock_end aoc_utilities::clock%clock_end program~problem_25->proc~clock_end proc~clock_start aoc_utilities::clock%clock_start program~problem_25->proc~clock_start proc~dag_destroy dag_module::dag%dag_destroy program~problem_25->proc~dag_destroy proc~dag_save_digraph dag_module::dag%dag_save_digraph program~problem_25->proc~dag_save_digraph proc~dag_set_edges dag_module::dag%dag_set_edges program~problem_25->proc~dag_set_edges proc~dag_set_vertex_info dag_module::dag%dag_set_vertex_info program~problem_25->proc~dag_set_vertex_info proc~dag_set_vertices dag_module::dag%dag_set_vertices program~problem_25->proc~dag_set_vertices proc~node_index problem_25::node_index program~problem_25->proc~node_index proc~number_of_lines_in_file aoc_utilities::number_of_lines_in_file program~problem_25->proc~number_of_lines_in_file proc~read_line aoc_utilities::read_line program~problem_25->proc~read_line proc~traverse~3 problem_25::traverse program~problem_25->proc~traverse~3 proc~split1 aoc_utilities::split1 interface~split->proc~split1 proc~split2 aoc_utilities::split2 interface~split->proc~split2 proc~unique32 aoc_utilities::unique32 interface~unique~2->proc~unique32 proc~unique64 aoc_utilities::unique64 interface~unique~2->proc~unique64 proc~dag_generate_digraph dag_module::dag%dag_generate_digraph proc~dag_save_digraph->proc~dag_generate_digraph none~set_edges dag_module::vertex%set_edges proc~dag_set_edges->none~set_edges proc~integer_to_string~2 dag_module::integer_to_string proc~dag_set_vertex_info->proc~integer_to_string~2 proc~traverse~3->proc~traverse~3 proc~add_edge dag_module::vertex%add_edge none~set_edges->proc~add_edge proc~set_edge_vector dag_module::vertex%set_edge_vector none~set_edges->proc~set_edge_vector proc~dag_generate_digraph->proc~integer_to_string~2 proc~expand_vector aoc_utilities::expand_vector proc~split1->proc~expand_vector proc~split2->proc~split1 interface~sort aoc_utilities::sort proc~unique32->interface~sort proc~unique64->interface~sort proc~sort_ascending aoc_utilities::sort_ascending interface~sort->proc~sort_ascending proc~sort_ascending_64 aoc_utilities::sort_ascending_64 interface~sort->proc~sort_ascending_64 proc~set_edge_vector->proc~add_edge interface~swap~2 aoc_utilities::swap proc~sort_ascending->interface~swap~2 proc~swap64 aoc_utilities::swap64 proc~sort_ascending_64->proc~swap64 interface~swap~2->proc~swap64 proc~swap32 aoc_utilities::swap32 interface~swap~2->proc~swap32 proc~swap_str aoc_utilities::swap_str interface~swap~2->proc~swap_str

Variables

Type Attributes Name Initial
integer :: iunit
integer :: n_lines
integer :: i
integer :: j
integer :: n_nodes
integer :: inode
integer :: inode2
character(len=:), allocatable :: line
type(string), dimension(:), allocatable :: vals
type(string), dimension(:), allocatable :: vals2
character(len=3) :: node1
character(len=3) :: node2
character(len=3), dimension(:), allocatable :: nodes
integer, dimension(:), allocatable :: inodedep
integer, dimension(:), allocatable :: icounts
character(len=*), parameter :: filetype = 'pdf'
type(dag) :: d
type(node_t), dimension(:), allocatable :: graph

index is the node number

logical, dimension(:), allocatable :: visited

Derived Types

type ::  node_t

Components

Type Visibility Attributes Name Initial
integer, public, dimension(:), allocatable :: connections

the ones connected to this one


Functions

pure function node_index(node)

find the node number for this name

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: node

Return Value integer


Subroutines

recursive subroutine traverse(i)

travere the graph and visit all the connected nodes

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i

Source Code

program problem_25

use aoc_utilities
use dag_module

implicit none

integer :: iunit, n_lines, i, j, n_nodes, inode, inode2
character(len=:),allocatable :: line
type(string),dimension(:),allocatable :: vals, vals2
character(len=3) :: node1, node2
character(len=3),dimension(:),allocatable :: nodes
integer,dimension(:),allocatable :: inodedep, icounts

character(len=*),parameter :: filetype = 'pdf'
type(dag) :: d

type :: node_t
    !character(len=3) :: name = ''
    integer,dimension(:),allocatable :: connections !! the ones connected to this one
end type node_t
type(node_t),dimension(:),allocatable :: graph !! index is the node number
logical,dimension(:),allocatable :: visited

call clk%tic()

! read the data:
! open(newunit=iunit, file='inputs/day25_test.txt', status='OLD')
open(newunit=iunit, file='inputs/day25.txt', status='OLD')
allocate(nodes(0))
n_lines = number_of_lines_in_file(iunit)
do i = 1, n_lines
    line = read_line(iunit)
    ! for starters, get a list of all the nodes
    vals = split(line,': ')
    node1 = vals(1)%str
    if (.not. any(nodes==node1)) nodes = [nodes,node1]
    vals2 = split(vals(2)%str, ' ')
    do j = 1, size(vals2)
        node2 = vals2(j)%str
        if (.not. any(nodes==node2)) nodes = [nodes,node2]
    end do
end do
rewind(iunit)
n_nodes = size(nodes)

! create a dag:
call d%set_vertices(n_nodes)
allocate(graph(n_nodes)) !...
do i = 1, n_nodes
    allocate(graph(i)%connections(0)) ! initialize
end do
do i = 1, n_lines
    line = read_line(iunit)
    ! for starters, get a list of all the nodes
    vals = split(line,': ')
    node1 = vals(1)%str
    inode = node_index(node1)
    !inode = findloc(nodes,node1)
    if (.not. any(nodes==node1)) nodes = [nodes,node1]
    vals2 = split(vals(2)%str, ' ')
    if (allocated(inodedep)) deallocate(inodedep)
    allocate(inodedep(0))
    do j = 1, size(vals2)
        node2 = vals2(j)%str
        inode2 = node_index(node2)

        !--------------------------------------------
        ! prune the ones by inspection by looking at the graph, opening in Inkscape,
        ! coloring the 3 lines and finding the nodes that connect them
        if ( (node1=='ljm' .and. node2=='sfd') .or. (node2=='ljm' .and. node1=='sfd') ) cycle
        if ( (node1=='gst' .and. node2=='rph') .or. (node2=='gst' .and. node1=='rph') ) cycle
        if ( (node1=='jkn' .and. node2=='cfn') .or. (node2=='jkn' .and. node1=='cfn') ) cycle
        !--------------------------------------------

        ! accumulate the graph:
        ! connection between inode <--> inodedep
        graph(inode)%connections  = [graph(inode)%connections, inode2]
        graph(inode2)%connections = [graph(inode2)%connections, inode]

        ! for the plot:
        inodedep = [inodedep, inode2]
    end do
    call d%set_edges(inode, inodedep)
end do

! define some styles for the GraphViz output:
do i = 1, n_nodes
    call d%set_vertex_info(i, label = nodes(i))
end do

! generate the GraphViz output:
call d%save_digraph('problem25.dot',rankdir='TB',dpi=300)
call d%destroy()
call execute_command_line('dot -Tpdf -o problem25.pdf problem25.dot')
    ! add to dot file:  !todo add this to daglib ...
    ! mindist=10
    ! ranksep=20

! count the ones connected to each node and get the unique two we need
allocate(visited(n_nodes))
allocate(icounts(0))
do i = 1, n_lines
    visited = .false.
    call traverse(i)
    icounts = unique([icounts, count(visited)])
    !write(*,*) i, icounts
end do
write(*,*) '25a:', product(icounts)

call clk%toc('25')

contains

    pure integer function node_index(node)
        !! find the node number for this name
        character(len=*),intent(in) :: node
        integer,dimension(1) :: idx
        idx = findloc(nodes,node)
        node_index = idx(1)
    end function node_index

    recursive subroutine traverse(i)
        !! travere the graph and visit all the connected nodes
        integer,intent(in) :: i
        integer :: j
        if (visited(i)) return
        visited(i) = .true.
        do j = 1, size(graph(i)%connections)
            call traverse(graph(i)%connections(j))
        end do
    end subroutine traverse

end program problem_25