Skip to content
Snippets Groups Projects
netcdf_io_module.f90 2.24 KiB
Newer Older
module netcdf_io_module
    use netcdf
    implicit none

    type :: io_struct
        integer :: ncid
        integer :: time_dimid, varid_time, varid_series
        logical :: is_open = .false.
        character(len=128) :: series_name = 'timeseries of variable'
        character(len=128) :: series_long_name = 'timeseries of some variable'
        character(len=128) :: series_units = 'unit'
    end type io_struct

contains
    subroutine open_netcdf(filename, ios, time_len)
        character(len=*), intent(in) :: filename
        type(io_struct), intent(out) :: ios
        integer, intent(in) :: time_len
        integer :: ierr

        ierr = nf90_create(filename, nf90_clobber, ios%ncid)
        if (ierr == nf90_noerr) then
            ios%is_open = .true.
            ierr = nf90_def_dim(ios%ncid, 'time', time_len, ios%time_dimid)
            ierr = nf90_def_var(ios%ncid, 'time', nf90_float, ios%time_dimid, ios%varid_time)
            ierr = nf90_def_var(ios%ncid, 'series', nf90_float, ios%time_dimid, ios%varid_series)
            ierr = nf90_put_att(ios%ncid, ios%varid_series, 'standard_name', ios%series_name)
            ierr = nf90_put_att(ios%ncid, ios%varid_series, 'long_name', ios%series_long_name)
            ierr = nf90_put_att(ios%ncid, ios%varid_series, 'units', ios%series_units)
            ierr = nf90_enddef(ios%ncid)
        else
            print *, 'Error opening file: ', ierr
            ios%is_open = .false.
        endif
    end subroutine open_netcdf

    subroutine write_series(ios, time_data, series_data)
        type(io_struct), intent(in) :: ios
        real, dimension(:), intent(in) :: time_data, series_data
        integer :: ierr

        if (.not. ios%is_open) then
            print *, "File is not open."
            return
        endif

        ierr = nf90_put_var(ios%ncid, ios%varid_time, time_data)
        ierr = nf90_put_var(ios%ncid, ios%varid_series, series_data)
        if (ierr /= nf90_noerr) then
            print *, 'Error writing data:', ierr
        endif
    end subroutine write_series

    subroutine close_netcdf(ios)
        type(io_struct), intent(inout) :: ios
        integer :: ierr

        ierr = nf90_close(ios%ncid)
        ios%is_open = .false.
    end subroutine close_netcdf
end module netcdf_io_module