training_data_files_m.f90 Source File


Files dependent on this one

sourcefile~~training_data_files_m.f90~~AfferentGraph sourcefile~training_data_files_m.f90 training_data_files_m.f90 sourcefile~fiats_m.f90 fiats_m.f90 sourcefile~fiats_m.f90->sourcefile~training_data_files_m.f90 sourcefile~training_data_files_s.f90 training_data_files_s.F90 sourcefile~training_data_files_s.f90->sourcefile~training_data_files_m.f90 sourcefile~concurrent-inferences.f90 concurrent-inferences.f90 sourcefile~concurrent-inferences.f90->sourcefile~fiats_m.f90 sourcefile~learn-addition.f90 learn-addition.F90 sourcefile~learn-addition.f90->sourcefile~fiats_m.f90 sourcefile~learn-exponentiation.f90 learn-exponentiation.F90 sourcefile~learn-exponentiation.f90->sourcefile~fiats_m.f90 sourcefile~learn-multiplication.f90 learn-multiplication.F90 sourcefile~learn-multiplication.f90->sourcefile~fiats_m.f90 sourcefile~learn-power-series.f90 learn-power-series.F90 sourcefile~learn-power-series.f90->sourcefile~fiats_m.f90 sourcefile~learn-saturated-mixing-ratio.f90 learn-saturated-mixing-ratio.F90 sourcefile~learn-saturated-mixing-ratio.f90->sourcefile~fiats_m.f90 sourcefile~saturated_mixing_ratio_m.f90 saturated_mixing_ratio_m.f90 sourcefile~learn-saturated-mixing-ratio.f90->sourcefile~saturated_mixing_ratio_m.f90 sourcefile~print-training-configuration.f90 print-training-configuration.F90 sourcefile~print-training-configuration.f90->sourcefile~fiats_m.f90 sourcefile~read-query-infer.f90 read-query-infer.f90 sourcefile~read-query-infer.f90->sourcefile~fiats_m.f90 sourcefile~saturated_mixing_ratio_m.f90->sourcefile~fiats_m.f90 sourcefile~train-and-write.f90 train-and-write.F90 sourcefile~train-and-write.f90->sourcefile~fiats_m.f90 sourcefile~write-read-infer.f90 write-read-infer.F90 sourcefile~write-read-infer.f90->sourcefile~fiats_m.f90

Source Code

! Copyright (c) 2023-2025, The Regents of the University of California
! Terms of use are as specified in LICENSE.txt
module training_data_files_m
  use julienne_m, only : string_t, file_t
  implicit none

  private
  public :: training_data_files_t

  type training_data_files_t
    private
    character(len=:), allocatable :: path_, inputs_prefix_, outputs_prefix_
    type(string_t), allocatable :: infixes_(:)
  contains
    procedure :: to_json
    procedure :: fully_qualified_inputs_files
    procedure :: fully_qualified_outputs_files
    procedure :: fully_qualified_time_file
    procedure :: path
    generic :: operator(==) => equals
    procedure, private :: equals
  end type

  interface training_data_files_t

    pure module function from_json(file) result(training_data_files)
      implicit none
      type(file_t), intent(in) :: file
      type(training_data_files_t) training_data_files
    end function

    pure module function from_components(path, inputs_prefix, outputs_prefix, infixes) result(training_data_files)
      implicit none
      character(len=*), intent(in)  :: path, inputs_prefix, outputs_prefix
      type(string_t), intent(in) :: infixes(:)
      type(training_data_files_t) training_data_files
    end function

  end interface

  interface

    pure module function path(self) result(training_data_file_path)
      implicit none
      class(training_data_files_t), intent(in) :: self
      character(len=:), allocatable :: training_data_file_path
    end function

    elemental module function equals(lhs, rhs) result(lhs_eq_rhs)
      implicit none
      class(training_data_files_t), intent(in) :: lhs, rhs
      logical lhs_eq_rhs
    end function

    pure module function to_json(self) result(file)
      implicit none
      class(training_data_files_t), intent(in) :: self
      type(file_t) file
    end function

    pure module function fully_qualified_inputs_files(self) result(names)
      implicit none
      class(training_data_files_t), intent(in) :: self
      type(string_t), allocatable :: names(:)
    end function

    pure module function fully_qualified_outputs_files(self) result(names)
      implicit none
      class(training_data_files_t), intent(in) :: self
      type(string_t), allocatable :: names(:)
    end function

    pure module function fully_qualified_time_file(self) result(name)
      implicit none
      class(training_data_files_t), intent(in) :: self
      type(string_t) name
    end function

  end interface

end module