Analyzing Time Series Data with Arrays#

The following program analyzes time series data using arrays.
Adapted from: “Modern Fortan” by Milan Curcic (Manning)

Program to Calculate the Gain of a Stock Price#

In file stock_gain.f90#

program stock_gain

  use mod_arrays, only: reverse
  use mod_io, only: read_stock

  implicit none

  character(len=4), allocatable ::  symbols(:)
  character(len=:), allocatable ::  time(:)
  real, allocatable             ::  open(:), high(:), low(:), &
                                    close(:), adjclose(:), volume(:)
                                    
  integer                       :: n                                    
  real                          :: gain

  symbols = ['AAPL', 'AMZN', 'CRAY', 'CSCO', 'HPQ ', &
             'IBM ', 'INTC', 'MSFT', 'NVDA', 'ORCL']
             
  do n = 1, size(symbols)

    call read_stock( &
      'data/' // trim(symbols(n)) // '.csv', &
      time, open, high, low, close, adjclose, volume)
    
      adjclose = reverse(adjclose)
      gain = (adjclose(size(adjclose)) - adjclose(1))
      
      if (n == 1) then
        print *, &
          time(size(time)) // ' through ' // time(1)
        
        print *, 'Symbol, Gain (USD), Relative Gain (%)'
        print *, '-------------------------------------'
      end if

      print *, symbols(n), gain, &
        nint(gain / adjclose(1) * 100)

  end do
    
end program stock_gain

In file mod_arrays.f90#

module mod_arrays

  ! Utility functions that operate on arrays.

  implicit none

  private
  public :: argsort, average, crossneg, crosspos, intdate, moving_average,&
            moving_std, reverse, std

contains

  pure function argsort(x) result(a)
    ! Returns indices that sort x from low to high.
    real, intent(in):: x(:)
    integer :: a(size(x))
    integer :: i, i0, tmp1
    real :: tmp2
    real :: xwork(size(x))
    a = [(real(i), i = 1, size(x))]
    xwork = x
    do i = 1, size(x) - 1
      i0 = minloc(xwork(i:), 1) + i - 1
      if (i0 /= i) then
        tmp2 = xwork(i)
        xwork(i) = xwork(i0)
        xwork(i0) = tmp2
        tmp1 = a(i)
        a(i) = a(i0)
        a(i0) = tmp1
      end if
    end do
  end function argsort

  pure real function average(x)
    ! Returns a average of x.
    real, intent(in) :: x(:)
    average = sum(x) / size(x)
  end function average

  pure function crossneg(x, w) result(res)
    ! Returns indices where input array x crosses its
    ! moving average with window w from positive to negative.
    real, intent(in) :: x(:)
    integer, intent(in) :: w
    integer, allocatable :: res(:)
    real, allocatable :: xavg(:)
    logical, allocatable :: greater(:), smaller(:)
    integer :: i
    res = [(i, i = 2, size(x))]
    xavg = moving_average(x, w)
    greater = x > xavg
    smaller = x < xavg
    res = pack(res, smaller(2:) .and. greater(:size(x)-1))
  end function crossneg

  pure function crosspos(x, w) result(res)
    ! Returns indices where input array x crosses its
    ! moving average with window w from negative to positive.
    real, intent(in) :: x(:)
    integer, intent(in) :: w
    integer, allocatable :: res(:)
    real, allocatable :: xavg(:)
    logical, allocatable :: greater(:), smaller(:)
    integer :: i
    res = [(i, i = 2, size(x))]
    xavg = moving_average(x, w)
    greater = x > xavg
    smaller = x < xavg
    res = pack(res, greater(2:) .and. smaller(:size(x)-1))
  end function crosspos

  pure elemental integer function intdate(t)
    ! Converts a time stamp in format YYYY-mm-dd to integer.
    character(len=10), intent(in) :: t
    character(len=8) :: str
    str = t(1:4) // t(6:7) // t(9:10)
    read(str, *) intdate
  end function intdate

  pure function moving_average(x, w) result(res)
    ! Returns the moving average of x with one-sided window w.
    real, intent(in) :: x(:)
    integer, intent(in) :: w
    real :: res(size(x))
    integer :: i, i1
    do i = 1, size(x)
      i1 = max(i-w, 1)
      res(i) = average(x(i1:i))
    end do 
  end function moving_average

  pure function moving_std(x, w) result(res)
    ! Returns the moving standard deviation of x with one-sided window w.
    real, intent(in) :: x(:)
    integer, intent(in) :: w
    real :: res(size(x))
    integer :: i, i1
    do i = 1, size(x)
      i1 = max(i-w, 1)
      res(i) = std(x(i1:i))
    end do 
  end function moving_std

  pure function reverse(x)
    ! Reverses the order of elements of x.
    real, intent(in) :: x(:)
    real :: reverse(size(x))
    reverse = x(size(x):1:-1)
  end function reverse

  pure real function std(x)
    ! Returns the standard deviation of x.
    real, intent(in) :: x(:)
    std = sqrt(average((x - average(x))**2))
  end function std

end module mod_arrays

In file mod_io.f90#

module mod_io

  ! A helper module for parsing stock price data in csv format.

  use mod_alloc, only: alloc

  implicit none

  private
  public :: read_stock, write_stock

contains

  integer function num_records(filename)
    ! Return the number of records (lines) of a text file.
    character(len=*), intent(in) :: filename
    integer :: fileunit
    open(newunit=fileunit, file=filename)
    num_records = 0
    do
      read(unit=fileunit, fmt=*, end=1)
      num_records = num_records + 1
    end do
    1 continue
    close(unit=fileunit)
  end function num_records

  subroutine read_stock(filename, time, open, high, low, close, adjclose, volume)
    ! Read daily stock prices from a csv file.
    character(len=*), intent(in) :: filename
    character(len=:), allocatable, intent(in out) :: time(:)
    real, allocatable, intent(in out) :: open(:), high(:), low(:),&
                                         close(:), adjclose(:), volume(:)
    integer :: fileunit, n, nm
    nm = num_records(filename) - 1
    if (allocated(time)) deallocate(time)
    allocate(character(len=10) :: time(nm))
    call alloc(open, nm)
    call alloc(high, nm)
    call alloc(low, nm)
    call alloc(close, nm)
    call alloc(adjclose, nm)
    call alloc(volume, nm)
    open(newunit=fileunit, file=filename)
    read(fileunit, fmt=*, end=1)
    do n = 1, nm
      read(fileunit, fmt=*, end=1) time(n), open(n),&
        high(n), low(n), close(n), adjclose(n), volume(n)
    end do
    1 close(fileunit)
  end subroutine read_stock

  subroutine write_stock(filename, time, price, mvavg, mvstd)
    ! Write derived stock data to file.
    character(len=*), intent(in) :: filename
    character(len=:), allocatable, intent(in) :: time(:)
    real, intent(in) :: price(:), mvavg(:), mvstd(:)
    integer :: fileunit, n
    open(newunit=fileunit, file=filename)
    do n = 1, size(time)
      write(fileunit, fmt=*) time(n), price(n), mvavg(n), mvstd(n)
    end do
    close(fileunit)
  end subroutine write_stock 

end module mod_io

Program Explanation#

The following explanation is given by “Code Copilot” within ChatGPT 4.

The stock_gain.f90 Fortran program calculates the gain of various stocks between two time points using their adjusted close prices. Here’s a breakdown of the code:

Modules Used#

  • mod_arrays: Provides a reverse function used to reverse arrays.

  • mod_io: Provides a read_stock function to read stock data from CSV files.

Data Structures#

  • Arrays for stock symbols, time periods, and financial metrics (open, high, low, close, adjusted close, volume) are dynamically allocated. The actual size of these arrays is set during runtime based on the data read from the CSV files.

Main Process#

  1. Symbol Initialization: A list of stock symbols is predefined.

  2. Loop Through Each Symbol:

    • For each symbol, it reads the corresponding stock data from a CSV file named after the stock symbol.

    • The adjusted close prices are reversed using the reverse function. This might be used to adjust the time order from most recent to oldest, or vice versa.

    • The gain is calculated as the difference between the final and initial adjusted close prices.

    • For the first stock, it prints the time period covered.

    • It outputs the stock symbol, the gain in USD, and the relative gain as a percentage.

Output#

  • The program prints a formatted output of the gains for each stock symbol over the specified period, showing both absolute and percentage changes.

This program makes use of separate modules for array manipulations and I/O operations, which simplifies the main program and focuses on the computation of stock gains.

The mod_arrays.f90 file defines a module called mod_arrays, which includes a variety of functions designed to perform common array manipulations and statistical computations. Here’s a detailed breakdown of each function provided in the module:

Functions in mod_arrays#

  • argsort(x): Returns indices that would sort the array x from low to high. This is useful for ordering data without changing the original array.

  • average(x): Calculates the average of the elements in the array x.

  • crossneg(x, w): Identifies indices where the array x crosses below its moving average of window size w. This function could be used to detect negative trends in time-series data.

  • crosspos(x, w): Similar to crossneg, but it finds indices where x crosses above its moving average. It’s used to identify positive trend shifts.

  • intdate(t): Converts a date string in the format YYYY-mm-dd to an integer format for easier handling.

  • moving_average(x, w): Computes the moving average of the array x using a one-sided window of size w. This function is essential for smoothing out time-series data.

  • moving_std(x, w): Computes the moving standard deviation of the array x, providing insights into the variability of the data over a specified window.

  • reverse(x): Reverses the elements of the array x. This is used in the main program to adjust the order of adjusted close prices.

  • std(x): Calculates the standard deviation of the array x, a measure of the spread or dispersion of the array elements around the mean.

Usage and Visibility#

  • All functions are declared as public which means they can be accessed from outside the module when it is included in other parts of the program.

  • The module uses pure functions, suggesting that these functions have no side effects (like modifying global variables), which is a desirable property in scientific computing for ensuring consistent and repeatable outcomes.

This module provides fundamental tools for data processing, especially useful in financial analysis or any scientific computing involving array data.

The mod_io.f90 module provides functionality for input/output operations, particularly focused on reading and writing stock data. Here’s a detailed overview of this module:

Functions and Subroutines#

  • num_records(filename): This function counts and returns the number of records (lines) in a text file, typically used to determine the size of data before allocating memory for variables.

  • read_stock(filename, time, open, high, low, close, adjclose, volume):

    • Reads daily stock prices from a CSV file specified by filename.

    • The stock data includes timestamps (time) and various price metrics (open, high, low, close, adjclose, and volume).

    • The subroutine first calculates the number of records using num_records, allocates memory for the data arrays, and then reads each line of the file, storing the data in the respective arrays.

  • write_stock(filename, time, price, mvavg, mvstd):

    • Writes derived stock data (like prices along with moving averages and moving standard deviations) to a file.

    • This is useful for outputting processed data, perhaps for reporting or further analysis.

Usage and Memory Management#

  • The module relies on another module mod_alloc for dynamic memory allocation (alloc function), though the contents of mod_alloc aren’t shown. This suggests a modular approach where memory management is abstracted away to improve code maintainability.

  • Memory allocation and deallocation are carefully handled in the read_stock subroutine to manage the memory efficiently and avoid memory leaks, especially important in Fortran where dynamic data structures are involved.

Design Considerations#

  • The I/O operations are encapsulated within this module, which separates the data handling logic from the computational logic found in other parts of the program.

  • Using separate subroutines for reading and writing data ensures that the module handles all aspects of file I/O, making it reusable for different parts of the application that need to process input or output data.

This module forms a critical component of the program by managing the flow of data in and out, ensuring that the main computational modules can focus solely on processing this data.

If you have more specific questions about how any part of the code works or if you need further details on any other aspect, feel free to ask!

Program Compilation and Execution#

The above program is compiled and run using Fortran Package Manager (fpm):

Build the Program using FPM (Fortran Package Manager)#

import os
root_dir = ""
root_dir = os.getcwd()

The following FPM configuration file (fpm.toml) was used:

name = "Analyzing_Time_Series_Data_with_Arrays"

[build]
auto-executables = true
auto-tests = true
auto-examples = true

[install]
library = false

[fortran]
implicit-typing = false
implicit-external = false
source-form = "free"

[[executable]]
name="Stock_Gain"
source-dir="app"
main="stock_gain.f90"
code_dir = root_dir + "/" + "Fortran_Code/Analyzing_Time_Series_Data_with_Arrays"
os.chdir(code_dir)
build_status = os.system("fpm build 2>/dev/null")

Run the Program using FPM (Fortran Package Manager)#

exec_status = \
    os.system("fpm run 2>/dev/null")
 2000-01-03 through 2018-05-14
 Symbol, Gain (USD), Relative Gain (%)
 -------------------------------------
 AAPL   184.594589            5192
 AMZN   1512.16003            1692
 CRAY   9.60000038              56
 CSCO   1.71649933               4
 HPQ    1.55270004               7
 IBM    60.9193039              73
 INTC   25.8368015              89
 MSFT   59.4120979             154
 NVDA   251.745300            6964
 ORCL   20.3501987              77