aoc_utilities Module

Helper classes and routines for Advent of Code

Author

  • Jacob Williams

hex string to int value. lowercase letters assumed! no error checking here!


Uses

  • module~~aoc_utilities~~UsesGraph module~aoc_utilities aoc_utilities iso_fortran_env iso_fortran_env module~aoc_utilities->iso_fortran_env

Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: wp = real64

default real kind [8 bytes]

integer, public, parameter :: ip = int64

default int kind

integer, private, parameter :: chunk_size = 100

for dynamic allocations

type(clock), public :: clk

a public clock to use for timing in the problems


Interfaces

public interface file_t

  • private function open_file(filename) result(f)

    Arguments

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

    Return Value type(file_t)

public interface sort

  • private subroutine sort_ascending(ivec)

    Sorts an integer array ivec in increasing order. Uses a basic recursive quicksort (with insertion sort for partitions with 20 elements).

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(inout), dimension(:) :: ivec
  • private subroutine sort_ascending_64(ivec)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ip), intent(inout), dimension(:) :: ivec

public interface parse

  • private function parse_nums64(line) result(ints)

    parse space-deliminated ip sequence (positive or negative)

    Arguments

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

    Return Value integer(kind=ip), dimension(:), allocatable

public interface split

  • private pure function split1(str, token) result(vals)

    Split a character string using a token. This routine is inspired by the Python split function.

    Example

       character(len=:),allocatable :: s
       type(string),dimension(:),allocatable :: vals
       s = '1,2,3,4,5'
       call split(s,',',vals)
    

    Arguments

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

    Return Value type(string), dimension(:), allocatable

  • private pure function split2(s, token) result(vals)

    Split a string, given a token.

    Arguments

    Type IntentOptional Attributes Name
    type(string), intent(in) :: s
    character(len=*), intent(in) :: token

    Return Value type(string), dimension(:), allocatable

public interface int

  • private pure elemental function string_to_int(me) result(i)

    Basic string to integer routine

    Arguments

    Type IntentOptional Attributes Name
    class(string), intent(in) :: me

    Return Value integer

  • private pure function char_to_int(str) result(i)

    Basic string to integer routine

    Arguments

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

    Return Value integer

  • private pure function char_to_int64(str, kind) result(i)

    Basic string to integer(ip) routine. Hacky hack just so we can overload as int()

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: str
    integer, intent(in) :: kind

    Return Value integer(kind=ip)

  • private pure function char_array_to_int(str_array) result(i)

    Character array to integer routine

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in), dimension(:) :: str_array

    example ['1','3'] --> 13

    Return Value integer

public interface str_to_int64

  • private pure elemental function string_to_int_64(me) result(i)

    Basic string to integer routine

    Arguments

    Type IntentOptional Attributes Name
    class(string), intent(in) :: me

    Return Value integer(kind=ip)

public interface unique

  • private function unique32(vec) result(vec_unique)

    Return only the unique values from vec.

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in), dimension(:) :: vec

    Return Value integer, dimension(:), allocatable

  • private function unique64(vec) result(vec_unique)

    Return only the unique values from vec.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ip), intent(in), dimension(:) :: vec

    Return Value integer(kind=ip), dimension(:), allocatable

public interface startswith

test if a string starts with a specified substring

  • private pure function startswith_cc(str, substring)

    starts with function for strings

    Arguments

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

    Return Value logical

  • private pure function startswith_ss(str, substring)

    Arguments

    Type IntentOptional Attributes Name
    type(string), intent(in) :: str
    type(string), intent(in) :: substring

    Return Value logical

  • private pure function startswith_sc(str, substring)

    Arguments

    Type IntentOptional Attributes Name
    type(string), intent(in) :: str
    character(len=*), intent(in) :: substring

    Return Value logical

  • private pure function startswith_cs(str, substring)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: str
    type(string), intent(in) :: substring

    Return Value logical

public interface swap

  • private pure elemental subroutine swap32(i1, i2)

    Swap two integer values.

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(inout) :: i1
    integer, intent(inout) :: i2
  • private pure elemental subroutine swap64(i1, i2)

    Swap two integer values.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ip), intent(inout) :: i1
    integer(kind=ip), intent(inout) :: i2
  • private pure elemental subroutine swap_str(i1, i2)

    Swap two character string values

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(inout) :: i1
    character(len=*), intent(inout) :: i2

public interface manhatten_distance

  • private pure function manhatten_distance_64(x1, y1, x2, y2)

    Manhattan distance between two ip points.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ip), intent(in) :: x1
    integer(kind=ip), intent(in) :: y1
    integer(kind=ip), intent(in) :: x2
    integer(kind=ip), intent(in) :: y2

    Return Value integer(kind=ip)

public interface get_indices

to get all the indices in a 2d array that match a value

  • private subroutine get_indices_in_char_array(array, val, iloc, jloc)

    return the indices of all the val elements in 2d array.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in), dimension(:,:) :: array
    character(len=1), intent(in) :: val
    integer, intent(out), dimension(:), allocatable :: iloc
    integer, intent(out), dimension(:), allocatable :: jloc
  • private subroutine get_indices_in_int_array(array, val, iloc, jloc)

    return the indices of all the val elements in 2d array.

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in), dimension(:,:) :: array
    integer, intent(in) :: val
    integer, intent(out), dimension(:), allocatable :: iloc
    integer, intent(out), dimension(:), allocatable :: jloc

Derived Types

type, public ::  clock

Components

Type Visibility Attributes Name Initial
integer(kind=ip), private :: begin
integer(kind=ip), private :: end
integer(kind=ip), private :: rate

Type-Bound Procedures

procedure, public :: tic => clock_start
procedure, public :: toc => clock_end

type, public ::  string

a type containing an allocatable character string. so we can have an array of strings of different lengths.

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: str

Type-Bound Procedures

procedure, public :: to_int => string_to_int ../../

convert to integer

procedure, public :: to_int_64 => string_to_int_64

type, public ::  file_t

Components

Type Visibility Attributes Name Initial
integer, public :: iunit = 0

Constructor

private function open_file (filename)

Finalizations Procedures

final :: close_file

Type-Bound Procedures

procedure, public :: n_lines
procedure, public :: read_line => read_line_from_file

type, public ::  int64_vec

an type that contains an allocatable ip array. so we can have an array of these.

Components

Type Visibility Attributes Name Initial
integer(kind=ip), public, dimension(:), allocatable :: vals

Functions

public function read_file_to_string(filename) result(str)

Arguments

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

Return Value character(len=:), allocatable

private function open_file(filename) result(f)

Arguments

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

Return Value type(file_t)

private function n_lines(me)

Arguments

Type IntentOptional Attributes Name
class(file_t), intent(in) :: me

Return Value integer

private function read_line_from_file(me) result(line)

Arguments

Type IntentOptional Attributes Name
class(file_t), intent(in) :: me

Return Value character(len=:), allocatable

private pure function char_to_int(str) result(i)

Basic string to integer routine

Arguments

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

Return Value integer

private pure elemental function string_to_int(me) result(i)

Basic string to integer routine

Arguments

Type IntentOptional Attributes Name
class(string), intent(in) :: me

Return Value integer

private pure elemental function string_to_int_64(me) result(i)

Basic string to integer routine

Arguments

Type IntentOptional Attributes Name
class(string), intent(in) :: me

Return Value integer(kind=ip)

private pure function char_to_int64(str, kind) result(i)

Basic string to integer(ip) routine. Hacky hack just so we can overload as int()

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: str
integer, intent(in) :: kind

Return Value integer(kind=ip)

public pure function int_to_string(i) result(s)

integer to string

Arguments

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

Return Value type(string)

public pure function int_to_str(i) result(s)

integer to string

Arguments

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

Return Value character(len=:), allocatable

private pure function char_array_to_int(str_array) result(i)

Character array to integer routine

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in), dimension(:) :: str_array

example ['1','3'] --> 13

Return Value integer

public pure function int_array_to_char_array(iarray) result(carray)

integer array to Character array

Arguments

Type IntentOptional Attributes Name
integer, intent(in), dimension(:,:) :: iarray

Return Value character(len=1), dimension(:,:), allocatable

public function read_file_to_char_array(filename, border) result(array)

Read a file into a 2d character array.

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
character(len=1), intent(in), optional :: border

if true, extra border is added with this char

Return Value character(len=1), dimension(:,:), allocatable

public function read_file_to_int_vec(filename) result(array)

read a file that is single string of ints into a vector

Arguments

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

Return Value integer, dimension(:), allocatable

public function read_file_to_int_array(filename) result(array)

Read a file into a 2d int array. Uses the '(*(I1))' format.

Arguments

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

Return Value integer, dimension(:,:), allocatable

public function read_file_to_integer_array(filename) result(iarray)

Read a file into an integer array (one element per line)

Arguments

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

Return Value integer, dimension(:), allocatable

public function read_file_to_integer64_array(filename) result(iarray)

Read a file into an ip integer array (one element per line)

Arguments

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

Return Value integer(kind=ip), dimension(:), allocatable

public function number_of_lines_in_file(iunit) result(n_lines)

Returns the number of lines in a file (assumed to be open)

Arguments

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

the file unit number (assumed to be open)

Return Value integer

the number of lines in the file

private pure function split2(s, token) result(vals)

Split a string, given a token.

Arguments

Type IntentOptional Attributes Name
type(string), intent(in) :: s
character(len=*), intent(in) :: token

Return Value type(string), dimension(:), allocatable

private pure function split1(str, token) result(vals)

Split a character string using a token. This routine is inspired by the Python split function.

Read more…

Arguments

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

Return Value type(string), dimension(:), allocatable

public function read_line(iunit, status_ok) result(line)

Reads the next line from a file.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: iunit
logical, intent(out), optional :: status_ok

true if no problems

Return Value character(len=:), allocatable

private function unique32(vec) result(vec_unique)

Return only the unique values from vec.

Arguments

Type IntentOptional Attributes Name
integer, intent(in), dimension(:) :: vec

Return Value integer, dimension(:), allocatable

private function unique64(vec) result(vec_unique)

Return only the unique values from vec.

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(in), dimension(:) :: vec

Return Value integer(kind=ip), dimension(:), allocatable

public function parse_ints(line) result(ints)

parse positive ints from a string that also includes text

Arguments

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

Return Value integer, dimension(:), allocatable

public function parse_ints64(line) result(ints)

Parse positive ints from a string that also includes text

Arguments

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

Return Value integer(kind=ip), dimension(:), allocatable

private function parse_nums64(line) result(ints)

parse space-deliminated ip sequence (positive or negative)

Arguments

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

Return Value integer(kind=ip), dimension(:), allocatable

private pure function startswith_cc(str, substring)

starts with function for strings

Arguments

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

Return Value logical

private pure function startswith_ss(str, substring)

Arguments

Type IntentOptional Attributes Name
type(string), intent(in) :: str
type(string), intent(in) :: substring

Return Value logical

private pure function startswith_sc(str, substring)

Arguments

Type IntentOptional Attributes Name
type(string), intent(in) :: str
character(len=*), intent(in) :: substring

Return Value logical

private pure function startswith_cs(str, substring)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: str
type(string), intent(in) :: substring

Return Value logical

public function is_number(c)

returns true if the character is a number from 0 to 9.

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: c

Return Value logical

public function is_not_number(c)

returns true if the character is not a number.

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: c

Return Value logical

public function str_to_array(s) result(a)

convert the character string to an array of characters

Arguments

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

Return Value character(len=1), dimension(len(s))

public pure function lcm(i, j)

LCM. based on code from NCAR Command Language

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(in) :: i
integer(kind=ip), intent(in) :: j

Return Value integer(kind=ip)

public pure function reverse(ivals) result(ireverse)

Reverse an ip vector

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(in), dimension(:) :: ivals

Return Value integer(kind=ip), dimension(size(ivals))

public pure function diff(ivals) result(idiff)

Difference ip vector

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(in), dimension(:) :: ivals

Return Value integer(kind=ip), dimension(:), allocatable

public function parea(x, y, nb)

given a sequence of nb points (x(i),y(i)). parea computes the area bounded by the closed polygonal curve which passes through the points in the order that they are indexed. the final point of the curve is assumed to be the first point given. therefore, it need not be listed at the end of x and y. the curve is not required to be simple.

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in) :: x(nb)
real(kind=wp), intent(in) :: y(nb)
integer, intent(in) :: nb

Return Value real(kind=wp)

private pure function manhatten_distance_64(x1, y1, x2, y2)

Manhattan distance between two ip points.

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(in) :: x1
integer(kind=ip), intent(in) :: y1
integer(kind=ip), intent(in) :: x2
integer(kind=ip), intent(in) :: y2

Return Value integer(kind=ip)

public pure function str_to_int_array_with_mapping(str, ichars, iints) result(array)

Convert a string to a numeric array by mapping characters to integers (user-specified)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: str
character(len=1), intent(in), dimension(:) :: ichars

characters to process

integer, intent(in), dimension(:) :: iints

int values of the chars

Return Value integer, dimension(:), allocatable

public pure function str_to_int64_array_with_mapping(str, ichars, iints) result(array)

Convert a string to a numeric array by mapping characters to integers (user-specified)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: str
character(len=1), intent(in), dimension(:) :: ichars

characters to process

integer(kind=ip), intent(in), dimension(:) :: iints

int values of the chars

Return Value integer(kind=ip), dimension(:), allocatable

public pure function hex2int(hex)

Arguments

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

Return Value integer

public pure function cross(r, v) result(c)

Cross product of two real 3x1 vectors

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in), dimension(3) :: r
real(kind=wp), intent(in), dimension(3) :: v

Return Value real(kind=wp), dimension(3)

public pure function num_digits(i)

return the number of digits in the integer

Arguments

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

Return Value integer


Subroutines

private subroutine close_file(me)

Arguments

Type IntentOptional Attributes Name
type(file_t), intent(inout) :: me

private subroutine clock_start(me)

Start the clock

Arguments

Type IntentOptional Attributes Name
class(clock), intent(inout) :: me

private subroutine clock_end(me, case_str)

Print runtime in milliseconds form the start of the clock.

Arguments

Type IntentOptional Attributes Name
class(clock), intent(inout) :: me
character(len=*), intent(in) :: case_str

description of the case

private subroutine sort_ascending(ivec)

Sorts an integer array ivec in increasing order. Uses a basic recursive quicksort (with insertion sort for partitions with 20 elements).

Arguments

Type IntentOptional Attributes Name
integer, intent(inout), dimension(:) :: ivec

private subroutine sort_ascending_64(ivec)

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(inout), dimension(:) :: ivec

private pure elemental subroutine swap32(i1, i2)

Swap two integer values.

Arguments

Type IntentOptional Attributes Name
integer, intent(inout) :: i1
integer, intent(inout) :: i2

private pure elemental subroutine swap64(i1, i2)

Swap two integer values.

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(inout) :: i1
integer(kind=ip), intent(inout) :: i2

private pure elemental subroutine swap_str(i1, i2)

Swap two character string values

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(inout) :: i1
character(len=*), intent(inout) :: i2

private pure subroutine expand_vector(vec, n, val, finished)

Add elements to the integer vector in chunks.

Arguments

Type IntentOptional Attributes Name
integer, intent(inout), dimension(:), allocatable :: vec
integer, intent(inout) :: n

counter for last element added to vec. must be initialized to size(vec) (or 0 if not allocated) before first call

integer, intent(in), optional :: val

the value to add to vec

logical, intent(in), optional :: finished

set to true to return vec as its correct size (n)

public pure subroutine locpt(x0, y0, x, y, n, l, m)

given a polygonal line connecting the vertices (x(i),y(i)) (i = 1,...,n) taken in this order. it is assumed that the polygonal path is a loop, where (x(n),y(n)) = (x(1),y(1)) or there is an arc from (x(n),y(n)) to (x(1),y(1)).

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in) :: x0
real(kind=wp), intent(in) :: y0
real(kind=wp), intent(in), dimension(n) :: x
real(kind=wp), intent(in), dimension(n) :: y
integer, intent(in) :: n
integer, intent(out) :: l
integer, intent(out) :: m

public subroutine inverse(a, ainv, status_ok)

inverse of a 2x2 matrix.

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in), dimension(2,2) :: a
real(kind=wp), intent(out), dimension(2,2) :: ainv
logical, intent(out) :: status_ok

private subroutine get_indices_in_char_array(array, val, iloc, jloc)

return the indices of all the val elements in 2d array.

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in), dimension(:,:) :: array
character(len=1), intent(in) :: val
integer, intent(out), dimension(:), allocatable :: iloc
integer, intent(out), dimension(:), allocatable :: jloc

private subroutine get_indices_in_int_array(array, val, iloc, jloc)

return the indices of all the val elements in 2d array.

Arguments

Type IntentOptional Attributes Name
integer, intent(in), dimension(:,:) :: array
integer, intent(in) :: val
integer, intent(out), dimension(:), allocatable :: iloc
integer, intent(out), dimension(:), allocatable :: jloc