! program eohcadd
!
! Adds all variables from eohc files to lsdiag file.
! Works with both single-case lsdiag and developmental lsdiag datafiles
! Written by Galina Chirokova  08/2018
!
! v1.1.1
!
!   Version history
! vCIRA2019_0.2.13
!   v2019.0.1.16 (GC)  - Addded writing ncoda_climo2 variables to lsdiags
!                      - removed extra set of climo and eohc char variable names
!                           now the char variable names are the same as 
!                           the abbreviation used in lsdiag
!                      - added climo variables to attributes file. Now scale for
!                           all variables is read from attributes file
!                           eohc_attributes.txt
!                      - added subroutine read_lsdiag_attributes.f90 - that
!                           is a general sub for reading varname and var scale
!                           from attributes file. Can be used for other lsdiag
!                           variables  
!   v2019.0.1.20 (GC)  - combined multiple subroutines for 
!                           getting eohc profile into a single subroutine 
!                               get_final_eohc_profile
!                           that gets interpolated eohc profile, filters it, and
!                           adds NSTA to that profile
!   v2019.0.1.21 (GC)  - combined multiple subroutines for 
!                           getting ncoda_climo2 profile into a single subroutine 
!                               get_final_ncodaclimo_profile
!   v2019.0.2.0 (GC)   - added option to use either list or filesystem to
!                        verify EOHC file existence. It is best to use list
!                        option: faster and more flexible
!                       - rearanged user options in the beginning of the file
!                         for a clean look  
!   v2019.0.2.3 (GC)   - replaced all print statements by write to lu_log_info
!                      - all logical units for opening files moved to main
!                               program
!                      - organized variable declaration to
!                                           input,oiutput,local
!                       - fixed minor bugs and error handling 
!   v2019.0.2.4 (GC)   - added option to specify 1st year for which eohc data
!                       exist and should be porocessed. That saves time by not serching for
!                       non-existing files
!                      - fixed bug to make sure each eohc file is read just once
!                      - cleaned up and fixed error messages
!                      - created 2nd debug file. Change "lu_log_info" to
!                           "lu_log_debug" for any unneded messages. Turn off
!                           creating debug file by seeting lu_log_debug = -1
!                      -  added option to read attributes file from operational
!                           location
!   v1.0.0 (MD)        - 5 Feb 2019 modifications for NHC computing environment.
!                        Documentation changes, modified log file output. 
!   v2019.0.2.6 (GC)   - Merged with Mark's changes
!   v2019.0.2.7 (GC)   - Added option to set NTMX, NDTX, NTFR, NDFR from NShay
!                           1995 - 2004 data to missing
!   v2019.0.2.8 (GC)   - Fixed bug in ncoda_climo2_module.f90 to correctly
!                           interpolate between Dec and Jan climo data
!   v2019.0.2.9 (GC)   - Fixed error handling bug in ncoda_climo2_module
!   v2019.0.2.10 (GC)   - Removed XLAT and XLON from the list of climo variables
!                           to use. These are only needed for debugging. 
!                           climo lats and lons are read
!                           from the headerof each climo file. 
!                        - redirected output of debug log to /dev/null
!   vCIRA2019_0.2.11 (GC) - Added flag min_days_old to specify how old shoudl be eohcdata.
!               that flag only works for developmental data
!   vCIRA2019_0.2.13 (GC) - Added to eohcadd_module subroutine get_basin_specific_params_from_upper
!                           to get basin-specific parameters. Used to se correct
!                           zonal periodicity flag izp
!                         - fixed minor formatting bug in printing llintsp
!                         output
!   vCIRA2019_1.0.0 (GC)   - added flag "use_generic_eohc_fname" - set to true
!                               to read eochdata from file "OHCYYYYMMDD.DAT"
!                          - fixed writing all climo variables
!                          - age is now calculated from the header data rather
!                          than from the EOHC filenames
!   v1.0.1 (GC)   - cleaned comments
!   v1.0.2 (GC)   - renamed variable n_data_arr to n_eohc_data_arr
!   v1.0.3 (GC)   - renamed variables: 
!                           ncvars to ncvars_max
!                           ncvars_lsdiag to ncvars
!   v1.1.0 (SS) - removed ioper flag, modified array sizes for 7 day
!
!   v1.1.1 (MD) - Extra write statement for debugging on ludgate (Jan 2024)
!                    
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! TODO - 
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

program eohcadd

    use eohc_module, only : get_eohc_var_names, &
        basin_upper_to_lower,&
        find_eohc_file,&
        get_final_eohc_profile,&
        make_lsdiag_mftline,&
        get_basin_specific_params_from_upper

    use ncoda_climo2_module, only : get_final_ncodaclimo_profile

    implicit none

    !25 max EOHC variables (26 used in climo since dsst is also used)
    integer,parameter :: n_eohc_data_arr_max = 25   
    ! number of actual variable in data array - MUST be also 25
    ! TODO: add option to make that variable 
    integer  :: n_eohc_data_arr

    !-----------------------------------------------------------------------
    !--- BEGIN - USER SHOULD ADJUST SETTINGS IN THIS SECTION---\/\/\/\/\/\/
    !
    ! control which variables are written to lsdiag
    ! write_all_eohc_vars 
    !        =  .true.  : will write all variables
    !        =  .false. : will write all variables except depth-averaged
    !        temperature, and NT32
    ! TODO: add more custom options
    ! - search for the flag in th ecode to make more specific adjustments
    ! RECOMMENDED SETTING: .false. 
    logical,parameter  :: write_all_eohc_vars = .false.
    
    !min days old to use previous eohc data
    !this setting is needed to use for development data similar to what is used
    !in real-time. In real-time eohc data are always at least 1 day old. 
    !Setting
    ! - min_days_old = 0 will find the most recent EOHC file
    ! - min_days_old = 1 will find the most recent 1-day old EOHC file. 
    ! - min_days_old = 2 will find the most recent 2-day old EOHC file. 
    ! the code will crash with an error if you set min_days_old > max_days_old   
    ! RECOMMENDED SETTING: 1
    integer, parameter :: min_days_old = 1

    !max days old to use previous eohc data
    !if no recent eohc data avialble
    ! RECOMMENDED SETTING: 7
    integer, parameter :: max_days_old = 7

    
    ! Distance (km) around the center for area-averaged SST
    ! TODO: move this to config file
    ! RECOMMENDED SETTING: 50.0
    real,parameter :: aakm = 50.0

    !---------
    ! default values for climo
    !                !adjust_climo = .true.
    !                !resolution = 'r050'
    !                !ncvars = 17
    !       true :  filter climo profile to remove bad values
    !       false :  do not filter climo profile to remov ebad values
    !---------
    ! set to 
    !       true :  filter out bad values from climo
    !       false :  do not filter out bad values from climo
    !           SHOULD be set to true in most cases
    !           setting this to 'false' can be only useful for
    !           code debugging
    ! RECOMMENDED SETTING: .true.
    logical,parameter :: adjust_climo = .true.
    
    ! number of climo variables to write to lsdiag file
    ! use only variables you need. 1st ncvars
    ! variables will be read and written to lsdiag
    ! refer to climo_var_names_arr for the names of the 1st 19 variables
    ! and rules for changing them
    ! max allowd number of vars is ncvars_max == 26
    ! RECOMMENDED SETTING: 17
    integer, parameter :: ncvars = 3
    !integer, parameter :: ncvars = 17
    
    ! resolution:
    !       'r025' - use .25 deg resolution for climo
    !       'r025' - use .50 deg resolution for climo
    character(len=4),parameter :: resolution = 'r050'
    
    ! option to use generic eohc file
    ! if set to true:
    !        - EOHC file 'OHCYYYYMMDD.DAT' will be used as input
    !           and the code wil NOT attept to find or check anything
    ! if set to false:
    !        - the code will find EOHC file from the list (if
    !        get_eohc_file_from_list = .true. or from the filesystem)
    ! MUST BE SET TO TRUE for REAL-TIME PROCESSING
    ! MUST BE SET TO FALSE for DEVELOPMENTAL PROCESSING
    logical,parameter :: use_generic_eohc_fname = .true.


    ! option to use EOHC file list to check if file exist:
    !  - true : list of files will be used to determine if file exists
    !  - false : inquire statemnt will be used to see if file exists in
    !               filesystem
    ! RECOMMENDED SETTING: .true.
    ! NOTE: is set to .true. then eohc_root will be auto_set to none
    ! is set to .false. then must provide correct eohc_root
    logical,parameter :: get_eohc_file_from_list = .true.

    ! upper-level eohc directory
    ! eohc root diretory, 
    ! ONLY needed if get_eohc_file_from_list = .false.
    ! #the code contains 2 options: 
    !1. get_eohc_file_from_list = .false.
    !     - the ecode will construct name of eohc files for day/time/basin
    !       and will use fortran "inquire" statement to check if file exists
    !       this optin assumes the following directory structure inside 
    !       eohc_root directory:
    !
    !       assumed diretory structure
    !        $eohc_root/2010/20100323/eohc_atl_20100329.dat
    !        $eohc_root/2010/20100323/eohc_pac_20100329.dat
    !        NOTE: this directory structure is created by the scripts making
    !            EOHC data
    !           files, but can be changed if needed 
    !2. get_eohc_file_from_list = .true.
    !       - the list of EOHC files for each basin should be created
    !       -  fortran code will construct the EOHC filename for day/time/basin
    !           and use lits of eohc files to check if the file exists
    !         NOTE: 
    !            - the option with using listis faster thus the defalt is set to
    !                use list
    !            - the option to use list can be used with different 
    !                directory structures, so is a little more flexible, 
    !                but requires creating of list files
    ! RECOMMENDED SETTING: 'NONE'
    character(len=200),parameter :: eohc_root  = 'NONE'


    ! logical unit number for eohc file
    integer,parameter :: lu_eohc = 21

    ! logical unit number for file containing
    ! list of eohc files
    integer,parameter :: lu_list = 22
    
    ! logical unit number for file containing
    ! list of eohc files
    integer,parameter :: lu_attr = 23
    
    ! logical unit number for log file
    ! 6 is standard output
    integer,parameter :: lu_log_info = 25
    ! log file for detailed debug messages
    ! set to negative number to turn off
    integer,parameter :: lu_log_debug = 26
    
    ! logical unit for ncodaclimo files
    integer,parameter :: lu_climo = 27
    
    ! logical unit for input lsdiag file
    integer,parameter :: ludat = 50
    ! logical unit for output lsdiag file
    integer,parameter :: ludat_new = 51

    ! eohcadd log filename
    character(len=11),parameter :: eohcadd_fname_log = 'eohcadd.log'
    ! eohcadd debug log filename
    ! -- use this to write debug log file
    ! character(len=17),parameter :: eohcadd_fname_debug = 'eohcadd_debug.log'
    ! use this to discard information written to debug log file 
    character(len=17),parameter :: eohcadd_fname_debug = '/dev/null'

    ! the first year for which eohc files are available
    ! to speed processing, if current year is less than
    ! ieohc_start_year, the code will NOT be seacrhing 
    ! for eohc files
    integer,parameter :: ieohc_start_year = 1995

    ! the 1st and last year of N Shay data
    ! All NTMX, NDTX, NTFR, NDFR values will be set to missing for 
    ! NShay data
    ! 1st year of NShay data
    integer,parameter ::  nshay_data_start_year = 1995
    ! last year of NShay data
    integer,parameter ::  nshay_data_end_year = 2004
    ! flag to reset NShay  NTMX, NDTX, NTFR, NDFR to missing
    logical,parameter ::  reset_nshay_to_missing = .true.

    ! flag for developmenal vs real-time data
    ! -- develop = .true. - code will stop on critical error
    !            = .false. - code will keep running on critical error
    logical,parameter :: develop = .false.


    ! local dir containing eohc_attributes.txt file
    character(len = 200) :: eohc_attributes_path_local = './'
   
    ! max possible number of eohc files for a single basin
    ! ( 365*(2019-2005) + 365*5 )  - estimated number of files
    ! for current+ 5 years
    !this MUST be defined in find_eohc_file to be able to save
    ! file list between runs
    !integer, parameter :: max_num_eohc_files = 10000
 
    ! this should be always set to FALSE for making 
    ! developmental and real-time operational lsdiags
    ! climo var names - experimental verion for testing only
    ! NEVER use that in real-time or operations
    ! RECOMMENDED SETTING: .false.
    logical,parameter :: experimental_climo  = .false.
    
    ! this should be always set to FALSE for making 
    ! developmental and real-time operational lsdiags
    ! set to false to add 2nd version of EOHC variables to the same lsdiag file.
    ! The variable names for 2nd verion will start with "KT" instead of "NT"
    ! RECOMMENDED SETTING: .false.
    logical,parameter  :: use_exp_eohc_variables = .false.

    !--- END - USER SHOULD ADJUST SETTINGS IN THIS SECTION-----/\/\/\/\/\/\
    !-----------------------------------------------------------------------

    ! header line for lsdiag
    character(len=165) :: hline
    ! regular line for lsdiag
    character(len=165) :: tline

    ! errors
    ! erro filtering EOHC profile
    ! = 0 if values were adjusted
    ! = 1 if d_floor and t_max needed for adjustment
    !       are not available
    integer :: ierr_adj
    ! master error read_eohc
    integer :: err_read_eohc_master
    ! llintsp error
    integer :: ierr_int
    ! error getting area averaged NSTA
    integer :: ierr_nsta
    ! error flags for
    ! open eohc list file
    integer :: ListOpenErr
    ! read eohc list file
    integer :: ListReadErr
    ! error reading EOHC attributes from file
    integer :: ierr_attr
    ! error reading non-header lsdiag line
    integer :: lsdiag_line_read_error

        
    ! upper case basin name, AL,EP,WP,IO,SH
    character(len=2) :: basin_upper
    ! lower case basin name, al, ep, wp, io,sh
    character(len=2) :: basin_lower
    !! eohc filename
    character(len=200) :: fn_eohc
    !
    !! generic eohc filename
    ! for real-time processing ONLY
    ! please keep th elength same as for fn_eohc variable
    character(len=200),parameter :: fn_gen_eohc='OHCYYYYMMDD.DAT'
    !
    ! array of variables names for EOHC
    character(len=4) :: var_names_arr(n_eohc_data_arr_max)
    ! saved array of variables names for EOHC
    ! thsi is used if there is no available recent EOHC file
    ! and the subroutine to get names is not called at current step
    character(len=4) :: var_names_arr_save(n_eohc_data_arr_max)
    ! var_names_arr + NSTA
    character(len=4) :: var_names_arr_final(n_eohc_data_arr_max+1)
    ! real missing values for eohc files
    real, parameter :: rmiss = -999.9
    !lat, lon from lsdiag header line
    real :: tlat_inp, tlon_inp
    ! data from eohc file header  
    !real :: flon_west, flon_east, fdlon, flat_south, flat_north,fdlat
    ! data from eohc file header  
    !real :: fihfcst,fsmin,fsmax,fkreacl
    ! eohc data source - NCODA - read from eohc file header
    character(len = 200) :: fohc_source
    ! 1st 4 letters of eohc filename
    character(len = 4) :: fn_eoch_4
 
    !2-digit year from lsdiag header
    integer :: iyear2_lsdiag
    !4-digit year from lsdiag header
    integer :: iyear4_lsdiag
    !2-digit month from lsdiag header
    integer :: imonth_lsdiag
    !2-digit day from lsdiag header
    integer :: iday_lsdiag
    !forecast hour from lsdiag header
    integer :: ifhour_lsdiag
    !
    ! data from EOHC file
    ! heaader date 
    integer :: iyear4_eohc, imonth_eohc, iday_eohc
    ! heaader hour
    integer :: ifhour_eohc


    ! iterator
    integer :: idata
    ! iterator
    integer :: i

    ! max number of lines allowed for a single lsdiag case
    integer,parameter :: nlines_max = 300
    ! lsdiag input filename 
    character(len=20) :: lsdiag_fname_inp
    ! lsdiag output filename 
    character(len=20) :: lsdiag_fname_out
    ! storm ATCF ID from lsdiag header
    character(len=8) :: stname
    ! case Vmax from lsdiag header
    integer :: ivmax
    ! case Pmin from lsdiag header
    integer :: imslp
    !real :: lat,lon

    !number of forecast times
    integer,parameter :: mft = 28
    character(len=1) :: loncon
    ! eohc_profile_arr  - contains eohc data for all 25 vars for all 20 forecst
    ! times for all 25 eohc variables + NSTA added after NSST
    real:: eohc_profile_arr(n_eohc_data_arr_max+1,-2:mft)
    ! eohc profile at given lat,lon
    real:: eohc_profile(n_eohc_data_arr_max)
    ! eohc_line for lsdiag
    character(len=165) :: eohc_line(n_eohc_data_arr_max)
    ! integer lat array for lsdiag
    integer:: ilat(-2:mft)
    ! integer lon array for lsdiag
    integer:: ilon(-2:mft)

     ! periodicity flag
     ! for AL and EP/CP set izp = 0
     ! for global  set izp = 1
     integer :: izp

    !iterators
    integer:: ivar,k
    ! current forecast time
    integer:: iftime
    ! current lsdiag line
    integer:: iline

    character(len=5) :: sname

    integer :: stat
    ! age of the EOHC data relative to date in lsdiag header from
    ! eohc filename
    integer :: eohc_days_old_ffilename
    ! age of the EOHC data relative to date in lsdiag header from 
    ! eohc file header
    integer :: eohc_days_old_fheader
    
    ! array of LSDIAG names for 25 eohc variables
    character(len=4) :: var_names_lsdiag_NT(n_eohc_data_arr_max)
    ! array of experimental LSDIAG names for 25 eohc variables
    character(len=4) :: var_names_lsdiag_KT(n_eohc_data_arr_max)
    ! array of LSDIAG names for 25 eohc variables +NSTA added after NSST
    character(len=4) :: var_names_lsdiag_NT_final(n_eohc_data_arr_max+1)
    ! array of experimental LSDIAG names for 25 eohc variables+KSTA added after KSST
    character(len=4) :: var_names_lsdiag_KT_final(n_eohc_data_arr_max+1)

    ! array of eohc_lines
    character(len=165) :: eohc_lines(n_eohc_data_arr_max+1)
   
    ! array of scales for variables to write to LSDIAG files 
    real :: var_scales_arr(n_eohc_data_arr_max)
    ! array of scales for variables to write to LSDIAG files +
    ! NSTA scale added after NSST scale
    real :: var_scales_arr_final(n_eohc_data_arr_max+1)
    ! integer missing value
    integer, parameter :: imiss = 9999
    
    ! temporary variable to store eohc variable name
    character(len=4) :: cvar
    
    ! filtered eohc profile at given lat,lon
    !  this is eohc_profile_filteres +NSTA added after NSST
    real:: eohc_profile_final(n_eohc_data_arr_max+1)

    ! NSTA estinmated for a single point
    real :: nsta

    ! !set to 
    !       true :  variable age info is not recorded
    !       false :  variable age info is recorded
    logical :: climo

    !integer :: max number of climo variables
    ! do NOT change, must be alwasy = 26
    integer, parameter :: ncvars_max = 26

    ! sum of all error returned by ncoda_climo2
    !   0 - normal output
    !  >0 - look inside subroutine get_ncodaclimo_profile.f90 for
    !           specific error
    !TODO: make sure these errors are output to the log file
    integer :: ierr_ncoda_climo2
    ! climo var names
    character(len=4) ::  climo_var_names_arr(ncvars_max)
    ! climo var names - experimental verion for testing only
    character(len=4) ::  climo_var_names_arr_exp(ncvars_max)
    ! climo var names for lsdiag file
    character(len=4) ::  climo_lsdiag_names_arr(ncvars_max)
    ! ncoda climo profile for a given point
    real :: climo_profile_arr(ncvars)
    ! ncoda climo profile for a given point for all forecast times
    real :: climo_profile_2d_arr(ncvars,-2:mft)
    ! ncoda climo variable scales for all variables in a profile
    real :: climo_scale_arr(ncvars_max)
    ! variable needed for compatibility with eohc data
    ! used in subroutine call, but is not used in subroutine
    integer :: climo_days_old
    ! array of climo lsdiag _lines
    character(len=165) :: climo_lines(ncvars_max)

    ! define IO lsdiag file names ---------------------
    if ( develop ) then
        lsdiag_fname_inp = 'lsdiag_devel_inp.dat'
        lsdiag_fname_out = 'lsdiag_devel_out.dat'
    else
        lsdiag_fname_inp = 'lsdiag_inp.dat'
        lsdiag_fname_out = 'lsdiag_out.dat'
    endif


    ! initialize age of EOHC data file to integer missing
    eohc_days_old_ffilename = imiss
    eohc_days_old_fheader = imiss
    
    ! ------------------------------------------------------------------------------------
    !    - number of EOHC variables to use
    !    - TODO: add logic to only use selected variables
    !        - NOTE: in many cases that logic is already included,
    !           but need to test that. THus for now must use 25 variables
    ! ------------------------------------------------------------------------------------
    !TODO - see if this could be made variable
    n_eohc_data_arr = 25

    ! ------------------------------------------------------------------------------------
    ! select and open IO data files
    ! ------------------------------------------------------------------------------------
  
    ! if log file is used, then delete old log and open new log 
    if ( lu_log_info /= 6 )  then
        ! open new log file
        open(file=eohcadd_fname_log,iostat=stat,unit=lu_log_info,form='formatted',status='replace')
    endif
    ! open debug log file
    open(file=eohcadd_fname_debug,iostat=stat,unit=lu_log_debug,form='formatted',status='replace')

    !open lsdiag

    !delete output file if exists
    open(file=lsdiag_fname_out,iostat=stat,unit=ludat_new,form='formatted',status='old')
    if (stat == 0) close(unit=ludat_new, status='delete')

    !open old (input) and new (output) file
    write(lu_log_info,*) 'INFO: eohcadd: will use lsdiag filenames ', &
                                    &lsdiag_fname_inp," ",lsdiag_fname_out
    open(file=lsdiag_fname_inp,unit=ludat,form='formatted',status='old')
    open(file=lsdiag_fname_out,unit=ludat_new,form='formatted',status='new')
        
    !get var_names_array
    !these var names will be used for the cases when no data is available 
    call get_eohc_var_names(n_eohc_data_arr_max,var_names_arr_save,&
                    lu_log_info,lu_log_debug)
    var_names_arr = var_names_arr_save
    ! ------------------------------------------------------------------------------------
    !define climo variables
    !           !rules
    !           1) - always define all 26 variables; put in the beginning the
    !               one you actually need
    !           2) - only the 1st ncvars_max variables will be used, and only
    !               data frm ncvar climo files will be read
    !           3) if use any of dml, d32-d16, d_tmax, then MUST
    !                   use d_floor
    !           4) if use any of d32 - d16 then MUST use Tmax
    climo_var_names_arr(1) = 'XDST'
    climo_var_names_arr(2) = 'XNST'
    climo_var_names_arr(3) = 'XOHC'
    climo_var_names_arr(4) = 'XDFR'
    climo_var_names_arr(5) = 'XTMX'
    climo_var_names_arr(6) = 'XDTX'
    climo_var_names_arr(7) = 'XDML'
    climo_var_names_arr(8) = 'XD30'
    climo_var_names_arr(9) = 'XD28'
    climo_var_names_arr(10) = 'XD26'
    climo_var_names_arr(11) = 'XD24'
    climo_var_names_arr(12) = 'XD22'
    climo_var_names_arr(13) = 'XD20'
    climo_var_names_arr(14) = 'XD18'
    climo_var_names_arr(15) = 'XD16'
    climo_var_names_arr(16) = 'XTFR'
    climo_var_names_arr(17) = 'XO20'

    climo_var_names_arr(18) = 'XD32'
    climo_var_names_arr(19) = 'XT05'
    climo_var_names_arr(20) = 'XT10'
    climo_var_names_arr(21) = 'XT16'
    climo_var_names_arr(22) = 'XT20'
    climo_var_names_arr(23) = 'XT25'
    climo_var_names_arr(24) = 'XT40'
    climo_var_names_arr(25) = 'XLON'
    climo_var_names_arr(26) = 'XLAT'
    ! ------------------------------------------------------------------------------------
    !    -  get scale and LSDIAG name for each EOHC variable
    ! ------------------------------------------------------------------------------------
    !get EOHC scale and LSDIAG name for each eohc var
    call read_lsdiag_attributes(var_names_arr, &
            var_names_lsdiag_KT,&
            eohc_attributes_path_local, &
            var_scales_arr,n_eohc_data_arr_max,lu_log_info,lu_log_debug,lu_attr,ierr_attr)
    if ( ierr_attr /= 0 ) then
        write(lu_log_info,*) 'CRITICAL ERROR: eohcadd: unable to read attributes &
                        &file; will STOP now.'
        stop
    endif
  
    !for compatibility with the previous version
    var_names_lsdiag_NT = var_names_arr
 
    ! set current eohc_file to 'none'
    fn_eohc = 'none'

    !get CLIMO scale and lsdiag names
    call read_lsdiag_attributes(climo_var_names_arr,&
            climo_var_names_arr_exp,&
            eohc_attributes_path_local,&
                climo_scale_arr,ncvars_max,lu_log_info,lu_log_debug,lu_attr,ierr_attr) 
    
    if ( ierr_attr /= 0 ) then
        write(lu_log_info,*) 'CRITICAL ERROR: eohcadd: unable to read attributes &
                        &file; will STOP now.'
        stop
    endif
    ! chose variable names to use for writing climo to lsdiags
    if ( experimental_climo ) then
         climo_lsdiag_names_arr = climo_var_names_arr_exp
    else 
         climo_lsdiag_names_arr = climo_var_names_arr
    endif 

    !write(lu_log_debug,*), 'DEBUG: eohcadd: Climo names ', climo_lsdiag_names_arr
    
    !
    !------------------------------------------------------------------------
    !------------------------------------------------------------------------
    !------------------------------------------------------------------------
    write(lu_log_info,*) 'INFO: eohcadd: Will start main lsdiag loop '
    !-------------------START main loop over cases in lsdiag file-----------
    !!!! This is the beginning of the loop through lsdiag cases  !!!
    !!!! the loop ends at 902 
    !read input lsdiag file
    ! the exit condition for this loop is error while reading HEAD line
    do while ( 1 .eq. 1 )

        ! ------------------------------------------------------------------------------------
        !    - read/write lsdiag HEAD line from old/to new file
        ! ------------------------------------------------------------------------------------
        !find and read header line from lsdiag
        read(ludat,200,end=902) hline
  200   format(a165)
        write(lu_log_debug,*) 'INFO: eohcadd: hline ',  hline

        if (hline(157:160) .ne. 'HEAD') then
!            cycle
!            write(lu_log_info,955)
            write(lu_log_info,*) 'INFO: eohcadd: hline ', hline
            write(*,955)
  955       format(/,'ERROR: eohcadd: Error reading HEAD line from input file')
            stop
        else
            !read the header line
            write(6,*) 'Start case ',hline(1:50)
            read(hline,300) sname,iyear2_lsdiag,imonth_lsdiag,iday_lsdiag,ifhour_lsdiag,&
                ivmax,tlat_inp,tlon_inp,&
                imslp,stname
  300       format(1x,a4,1x,3(i2),1x,i2,2x,i3,f7.1,f7.1,1x,i4,1x,a8)
        endif

        !only works for the years between 1951 and 2050
        if (iyear2_lsdiag .gt. 50) then
            iyear4_lsdiag = 1900+iyear2_lsdiag
        else
            iyear4_lsdiag = 2000+iyear2_lsdiag
        endif

        !write header line to a new file
        write(ludat_new,500) hline
  500 format(a165)

        ! ------------------------------------------------------------------------------------
        !    - create eohc filename using information from HEAD line
        !    - check if EOHC file with that name exists
        !    - if EOHC file not available, find the most recent available eohc
        !        file, but at least min_days_old and no older than max_days_old
        !    - compare found eohc filename with the saved eohcfilename to
        !       determine in new eohc file should be opened
        ! ------------------------------------------------------------------------------------
        basin_upper=stname(1:2)

        ! get basin specific parameters
        call get_basin_specific_params_from_upper(basin_upper,&
                izp,&
                lu_log_info,lu_log_debug)

        !get date from HEAD lsdiag

        !!--- START example how values should look like -----
        !!basin_upper='AL'
        !!iyear4_lsdiag = 2017
        !!imonth_lsdiag = 8
        !!iday_lsdiag = 15
        !
        !!get lat,lon from HEAD lsdiag
        !
        !!tlat_inp = 30.6
        !!tlon_inp = -75.3
        !!---END  example how values should look like -----

        !find eohc file corresponding to HEAD lsdiag case
        call  basin_upper_to_lower(basin_upper,basin_lower,&
                                        lu_log_info,lu_log_debug)

        ! make sure the time range for EOHC file is valid
        if ( min_days_old >= max_days_old ) then
            write(lu_log_debug,*) 'CRITICAL ERROR: eohcadd: Will STOP now. &
                    & to find EOHC files I need min_days_old < max_days_old. &
                    & Instead I got min_days_old, max_days_old = ', &
                        min_days_old, max_days_old
        endif

        ! find EOHC file or use generic eohc file
        if ( use_generic_eohc_fname ) then
            fn_eohc = fn_gen_eohc
            write(lu_log_info,*) 'INFO: eohcadd: will use generic eohc file ', trim(fn_eohc)
        else
            ! non-operational,use this code to find most recent eohc file
            ! and calculate eohc_file_age in days
            ! if get_eohc_file_from_list == .true. then 
            !           eohc_root will be set to NONE
            call find_eohc_file(eohc_root, get_eohc_file_from_list, &
                    basin_upper, iyear4_lsdiag, imonth_lsdiag, iday_lsdiag, &
                    ieohc_start_year, min_days_old, max_days_old,&
                    fn_eohc, eohc_days_old_ffilename,lu_log_info,lu_log_debug,lu_list,&
                    ListOpenErr,ListReadErr)
           
            write(lu_log_debug,*) 'INFO: eohcadd: error summary for find_eohc_file. &
                        & ListOpenErr,ListReadErr ', ListOpenErr,ListReadErr
            write(lu_log_info,*) 'INFO: eohcadd: found eohc file ', trim(fn_eohc)
        endif
       
        ! ------------------------------------------------------------------------------------
        !    - read/write everything from HEAD to LAt, LON
        !    - and save ilat(k) and ilon(k) - these arrays will be used
        !       to interpolate EOHC data at each point
        ! ------------------------------------------------------------------------------------
        ! initialize lat/lon arrays to missing 
        ilat(:) = imiss
        ilon(:) = imiss
        !read lat, lon at each forecast time from lsdiag
        !write HEAD and everything before LON and LON to new lsdiag
        do iline = 1, nlines_max
            ! this loop wil EXIT after reading ' LON' line
            ! ' LON' MUST be after ' LAT' line
            read(ludat,500,iostat=lsdiag_line_read_error) tline
            ! code will get here if there is an error while reading LSDIAG header 
            if ( lsdiag_line_read_error /= 0 ) then
                write(lu_log_info,*) 'CRITICAL ERROR: eohcadd: &
                    &error reading ldsiag non-header line tline(157:160) ', tline
                stop
            endif
            if ( (tline(157:160) .ne. 'LAT ') .and.  (tline(157:160) .ne. 'LON ') ) then
                !write line to a new file
                write(ludat_new,500) tline
            else
                !read LAT
  401           format(31(1x,i4), a4 , 5x ) 
  402           format(31(1x,i4), a4 , 5x ) 
                select case (tline(157:160))
                    case ('LAT ')
                        ! read 'LAT ' from old lsdiag
                        read (tline, 401) ( ilat(k), k = -2,mft )
                        ! write 'LAT ' to new lsdiag
                        write(ludat_new,500) tline
                    case ('LON ')
                        ! read 'LON ' from old lsdiag
                        read (tline, 401) ( ilon(k), k = -2,mft )
                        ! write 'LON ' to new lsdiag
                        write(ludat_new,500) tline
                        !next line assumes LON MUST be after LAT
                        exit
                end select
                write(lu_log_debug,*) 'INFO: eohcadd: tline ', tline
                write(lu_log_debug,*) 'INFO: eohcadd: ilat ',  ( ilat(k), k = -2,mft )
!                if (tline(157:160) .ne. 'LAT ') then
!                    read (tline, 401) ( ilat(k), k = -2,20 )
!  401               format(23(1x,i4), 'LAT', 5x ) 
!                endif 
            endif
        enddo


        ! ------------------------------------------------------------------------------------
        !    -  populate array climo_profile_2d_arr(ncvars_max,-2:mft) 
        !           that array contains all 26 (25 +dsst) ncoda climo variables for all forecast times 
        !           for a single lsdiag case
        ! ------------------------------------------------------------------------------------

        ! initialize climo_profile to missing 
        climo_profile_2d_arr(:,:) = rmiss     

        write(lu_log_debug,*) 'INFO: eohcadd: climo_var_names_arr ', climo_var_names_arr
        call get_final_ncodaclimo_profile(mft,ilon,ilat, adjust_climo,&
                        climo_var_names_arr,iyear4_lsdiag,imonth_lsdiag,iday_lsdiag,resolution,&
                        ncvars_max,ncvars,&
                        ierr_ncoda_climo2,&
                        climo_profile_2d_arr, &
                        lu_log_info, lu_log_debug,lu_climo,develop)
        !write(lu_log_debug,*) 'INFO: eohcadd: climo_var_names_arr ', climo_var_names_arr

        ! ------------------------------------------------------------------------------------
        !    -  populate array eohc_profile_arr(n_eohc_data_arr,-2:mft) 
        !           that array contains all 25 EOHC variables for all forecast times 
        !           for a single lsdiag case
        ! ------------------------------------------------------------------------------------

        ! initialize eohc_profile_arr to missing - for all
        !       forecast times for all eohc variables for current lsdiag case 
        eohc_profile_arr(:,:) = rmiss

        !Add new write statement for debugging
        write(lu_log_info,*) 'INFO: call get_final_eohc_profile'

        call get_final_eohc_profile(mft,ilon,ilat,&
                            iyear4_lsdiag,imonth_lsdiag,iday_lsdiag,ifhour_lsdiag,&
                            fn_eohc,lu_eohc,&
                            eohc_profile,aakm,tlat_inp,tlon_inp,&
                            n_eohc_data_arr_max,n_eohc_data_arr,var_names_arr,&
                            var_names_lsdiag_KT_final,var_names_lsdiag_KT,&
                            var_names_lsdiag_NT_final,var_names_lsdiag_NT,&
                            var_scales_arr,var_scales_arr_final,nsta,&
                            eohc_profile_arr,eohc_days_old_fheader,&
                            var_names_arr_save,lu_log_info,lu_log_debug,ierr_adj,&
                            err_read_eohc_master,ierr_int,ierr_nsta,&
                            nshay_data_start_year,&
                            nshay_data_end_year,&
                            reset_nshay_to_missing,&
                            develop,izp,&
                            iyear4_eohc, imonth_eohc, iday_eohc,&
                            ifhour_eohc)                            


        write(lu_log_info,*) 'INFO: eohcadd: ', & 
                    & " lsdiag header line hline  =  ", hline
        write(lu_log_info,*) 'INFO: eohcadd: error summary for get_final_eohc_profile. &
                    & errors: ierr_adj,err_read_eohc_master,ierr_int,ierr_nsta ',&
                    &ierr_adj,err_read_eohc_master,ierr_int,ierr_nsta
        ! ------------------------------------------------------------------------------------
        !    -  make LSDIAG line for each ncodaclimo variable, incuding XSST
        ! ------------------------------------------------------------------------------------
        ! make LSDIAG line for each EOHC variables
        ! write to lsdiag variables for NCODA starting with 'NT' - that
        ! should be used to make developmental lsdiag files
        !set climo_days_old to zero - for climo that variable is not needed
        ! and will not be written to the output file
        climo_days_old = 0
        ! write climo lines. .true. is for option to use climo: for climo the
        ! variable age is not recorded
        write(lu_log_debug,*) 'INFO: eohcadd: climo_var_names_arr ', climo_var_names_arr
        do ivar = 1,ncvars
            call make_lsdiag_mftline(mft,climo_profile_2d_arr(ivar,:),climo_lsdiag_names_arr(ivar),&
                    climo_lines(ivar),climo_scale_arr(ivar),climo_days_old, &
                    ilat,ilon,.true.,lu_log_info,lu_log_debug,&
                    iyear4_lsdiag, &
                    reset_nshay_to_missing, &
                    nshay_data_start_year,&
                    nshay_data_end_year)
        enddo
        !write(lu_log_debug,*) 'INFO: eohcadd: climo_lines ', climo_lines
        ! ------------------------------------------------------------------------------------
        !    -  make LSDIAG line for each eohc variable
        ! ------------------------------------------------------------------------------------
        ! make LSDIAG line for each EOHC variables
        ! write EOHC lines. .false. is for option to NOT use climo: for climo the
        ! variable age is not recorded; for real data additional field with
        ! variable age is recorded

        if ( .not. use_exp_eohc_variables ) then
            ! write to lsdiag variables for NCODA starting with 'NT' - that
            ! should be used to make developmental lsdiag files
            do ivar = 1,n_eohc_data_arr+1
                call make_lsdiag_mftline(mft,eohc_profile_arr(ivar,:),var_names_lsdiag_NT_final(ivar),&
                        eohc_lines(ivar),var_scales_arr_final(ivar),eohc_days_old_fheader, &
                            ilat,ilon,.false.,lu_log_info, lu_log_debug,&
                            iyear4_lsdiag, &
                            reset_nshay_to_missing, &
                            nshay_data_start_year,&
                            nshay_data_end_year)
            enddo
        else
            ! write to lsdiag EXPERIMENTAL variables for NCODA starting with 'KT' - that
            ! can be used for testing is 2nd verion of th esame variable need to
            ! be written
            ! write EOHC lines. .false. is for option to NOT use climo: for climo the
            ! variable age is not recorded; for real data additional field with
            ! variable age is recorded
            do ivar = 1,n_eohc_data_arr+1
                call make_lsdiag_mftline(mft,eohc_profile_arr(ivar,:),var_names_lsdiag_KT_final(ivar),&
                        eohc_lines(ivar),var_scales_arr_final(ivar),eohc_days_old_fheader, &
                            ilat,ilon,.false.,lu_log_info,lu_log_debug,&
                            iyear4_lsdiag, &
                            reset_nshay_to_missing, &
                            nshay_data_start_year,&
                            nshay_data_end_year)
            enddo
        endif

        ! ------------------------------------------------------------------------------------
        !    -  read from the old and write to the new LSDIAG everything between 
        !       "LON " and "LAST " from the old lsdiag
        !     - write all eohc lines to LSDIAG
        !     - write 'LAST'  line to LSDIAG
        ! ------------------------------------------------------------------------------------
        !write everything between LON and LAST to new lsdiag
        do iline = 1, nlines_max
            ! read old line
            read(ludat,500,iostat=lsdiag_line_read_error) tline
            ! code will get here if there is an error while reading LSDIAG header 
            if ( lsdiag_line_read_error /= 0 ) then
                write(lu_log_info,*) 'ERROR: eohcadd: &
                    &error reading ldsiag non-header line tline(157:160) ', tline
                stop
            endif
            ! write either current line or new EOHC lines
            if (tline(157:160) .ne. 'LAST') then
                !write line from the old file to a new file
                write(ludat_new,500) tline
            else
                !write new lines for all climo variables
                do ivar = 1,ncvars
                    write(ludat_new,500) climo_lines(ivar)
                enddo
                !write new lines for all EOHC variables
                if ( write_all_eohc_vars ) then
                    do ivar = 3,n_eohc_data_arr+1
                        write(ludat_new,500) eohc_lines(ivar)
                    enddo
                else
                    ! write everything except DAVT, NO20, and NT32
                    ! TODO: add a better way to write only needed
                    !     variables
                    ! use variable nuumbers from subroutine
                    ! variables numbers
                    !  1 - NLON
                    !  2 - NLAT
                    !  3 - NSST
                    !  4 - NSTA
                    !  5 - NTMX
                    !  6 - NDTX
                    !  7 - NDML
                    !  8 - ND32
                    !  9 - ND30
                    ! 10 - ND28
                    ! 11 - ND26
                    ! 12 - ND24
                    ! 13 - ND22
                    ! 14 - ND20
                    ! 15 - ND18
                    ! 16 - ND16
                    ! 17 - NDFR
                    ! 18 - NTFR
                    ! 19 - NOHC
                    ! 20 - NO20
                    ! 21 - NT05
                    ! 22 - NT10
                    ! 23 - NT16
                    ! 24 - NT20
                    ! 25 - NT25
                    ! 26 - NT40
                    do ivar = 3,20
                        !if (eohc_lines(ivar)(157:160) /= 'NT32' ) then
                        if (ivar /= 8 ) then
                            write(ludat_new,500) eohc_lines(ivar)
                        endif
                    enddo
                endif
                !write last line
                write(ludat_new,500) tline
                exit
            endif
        enddo
    enddo
    902 continue
    !-------------------END main loop over cases in lsdiag file-----------
    !---------------------------------------------------------------------
    !---------------------------------------------------------------------
    !---------------------------------------------------------------------
    close(unit=ludat,status='keep')
    close(unit=ludat_new, status='keep')


    if ( lu_log_info /= 6 )  then
        !close log file
        close(unit=lu_log_info,status='keep')
    endif
    close(unit=lu_log_debug,status='keep')

end program eohcadd