MODULE tl_wrt_his_mod ! !git $Id$ !svn $Id: tl_wrt_his.F 1189 2023-08-15 21:26:58Z arango $ !================================================== Hernan G. Arango === ! Copyright (c) 2002-2023 The ROMS/TOMS Group ! ! Licensed under a MIT/X style license ! ! See License_ROMS.md ! !======================================================================= ! ! ! This module writes fields into output tangent linear history file ! ! using either the standard NetCDF library or the Parallel-IO (PIO) ! ! library. ! ! ! !======================================================================= ! USE mod_param USE mod_parallel USE mod_coupling USE mod_grid USE mod_iounits USE mod_mixing USE mod_ncparam USE mod_ocean USE mod_scalars USE mod_stepping ! USE nf_fwrite2d_mod, ONLY : nf_fwrite2d USE nf_fwrite3d_mod, ONLY : nf_fwrite3d USE strings_mod, ONLY : FoundError ! implicit none ! PUBLIC :: tl_wrt_his PRIVATE :: tl_wrt_his_nf90 ! CONTAINS ! !*********************************************************************** SUBROUTINE tl_wrt_his (ng, tile) !*********************************************************************** ! ! Imported variable declarations. ! integer, intent(in) :: ng, tile ! ! Local variable declarations. ! integer :: LBi, UBi, LBj, UBj ! character (len=*), parameter :: MyFile = & & "ROMS/Tangent/tl_wrt_his.F" ! !----------------------------------------------------------------------- ! Write out history fields according to IO type. !----------------------------------------------------------------------- ! LBi=BOUNDS(ng)%LBi(tile) UBi=BOUNDS(ng)%UBi(tile) LBj=BOUNDS(ng)%LBj(tile) UBj=BOUNDS(ng)%UBj(tile) ! SELECT CASE (TLM(ng)%IOtype) CASE (io_nf90) CALL tl_wrt_his_nf90 (ng, tile, & & LBi, UBi, LBj, UBj) CASE DEFAULT IF (Master) WRITE (stdout,10) TLM(ng)%IOtype exit_flag=3 END SELECT IF (FoundError(exit_flag, NoError, 118, MyFile)) RETURN ! 10 FORMAT (' TL_WRT_HIS - Illegal output file type, io_type = ',i0, & & /,14x,'Check KeyWord ''OUT_LIB'' in ''roms.in''.') ! RETURN END SUBROUTINE tl_wrt_his ! !*********************************************************************** SUBROUTINE tl_wrt_his_nf90 (ng, tile, & & LBi, UBi, LBj, UBj) !*********************************************************************** ! USE mod_netcdf ! ! Imported variable declarations. ! integer, intent(in) :: ng, tile integer, intent(in) :: LBi, UBi, LBj, UBj ! ! Local variable declarations. ! integer :: Fcount, gfactor, gtype, status integer :: i, itrc, j, k ! real(dp) :: scale real(r8) :: Tval(1) ! character (len=*), parameter :: MyFile = & & "ROMS/Tangent/tl_wrt_his.F"//", tl_wrt_his_nf90" ! SourceFile=MyFile ! !----------------------------------------------------------------------- ! Write out tangent linear fields. !----------------------------------------------------------------------- ! IF (FoundError(exit_flag, NoError, 163, MyFile)) RETURN ! ! Set grid type factor to write full (gfactor=1) fields or water ! points (gfactor=-1) fields only. ! gfactor=1 ! ! Set time record index. ! TLM(ng)%Rindex=TLM(ng)%Rindex+1 Fcount=TLM(ng)%load TLM(ng)%Nrec(Fcount)=TLM(ng)%Nrec(Fcount)+1 ! ! Report. ! IF (Master) WRITE (stdout,10) kstp(ng), nrhs(ng), TLM(ng)%Rindex ! ! If requested, set time index to recycle time records in the tangent ! linear file. ! IF (LcycleTLM(ng)) THEN TLM(ng)%Rindex=MOD(TLM(ng)%Rindex-1,2)+1 END IF ! ! Write out model time (s). ! IF (LwrtPER(ng)) THEN Tval(1)=REAL(TLM(ng)%Rindex,r8)*day2sec ELSE Tval(1)=time(ng) END IF CALL netcdf_put_fvar (ng, iTLM, TLM(ng)%name, & & TRIM(Vname(1,idtime)), tval, & & (/TLM(ng)%Rindex/), (/1/), & & ncid = TLM(ng)%ncid, & & varid = TLM(ng)%Vid(idtime)) IF (FoundError(exit_flag, NoError, 215, MyFile)) RETURN ! ! Write out free-surface (m) ! IF (Hout(idFsur,ng)) THEN scale=1.0_dp gtype=gfactor*r2dvar status=nf_fwrite2d(ng, iTLM, TLM(ng)%ncid, idFsur, & & TLM(ng)%Vid(idFsur), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, scale, & & GRID(ng) % rmask, & & OCEAN(ng) % tl_zeta(:,:,kstp(ng))) IF (FoundError(status, nf90_noerr, 393, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idFsur)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! ! Write out 2D U-momentum component (m/s). ! IF (Hout(idUbar,ng)) THEN scale=1.0_dp gtype=gfactor*u2dvar status=nf_fwrite2d(ng, iTLM, TLM(ng)%ncid, idUbar, & & TLM(ng)%Vid(idUbar), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, scale, & & GRID(ng) % umask_full, & & OCEAN(ng) % tl_ubar(:,:,kstp(ng))) IF (FoundError(status, nf90_noerr, 465, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idUbar)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF ! status=nf_fwrite2d(ng, iTLM, TLM(ng)%ncid, idUfx1, & & TLM(ng)%Vid(idUfx1), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, scale, & & GRID(ng) % umask_full, & & COUPLING(ng) % tl_DU_avg1) IF (FoundError(status, nf90_noerr, 523, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idUfx1)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF ! status=nf_fwrite2d(ng, iTLM, TLM(ng)%ncid, idUfx2, & & TLM(ng)%Vid(idUfx2), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, scale, & & GRID(ng) % umask_full, & & COUPLING(ng) % tl_DU_avg2) IF (FoundError(status, nf90_noerr, 540, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idUfx2)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! ! Write out 2D V-momentum component (m/s). ! IF (Hout(idVbar,ng)) THEN scale=1.0_dp gtype=gfactor*v2dvar status=nf_fwrite2d(ng, iTLM, TLM(ng)%ncid, idVbar, & & TLM(ng)%Vid(idVbar), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, scale, & & GRID(ng) % vmask_full, & & OCEAN(ng) % tl_vbar(:,:,kstp(ng))) IF (FoundError(status, nf90_noerr, 594, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idVbar)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF ! status=nf_fwrite2d(ng, iTLM, TLM(ng)%ncid, idVfx1, & & TLM(ng)%Vid(idVfx1), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, scale, & & GRID(ng) % vmask_full, & & COUPLING(ng) % tl_DV_avg1) IF (FoundError(status, nf90_noerr, 652, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idVfx1)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF ! status=nf_fwrite2d(ng, iTLM, TLM(ng)%ncid, idVfx2, & & TLM(ng)%Vid(idVfx2), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, scale, & & GRID(ng) % vmask_full, & & COUPLING(ng) % tl_DV_avg2) IF (FoundError(status, nf90_noerr, 669, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idVfx2)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! ! Write out 3D U-momentum component (m/s). ! IF (Hout(idUvel,ng)) THEN scale=1.0_dp gtype=gfactor*u3dvar status=nf_fwrite3d(ng, iTLM, TLM(ng)%ncid, idUvel, & & TLM(ng)%Vid(idUvel), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, 1, N(ng), scale, & & GRID(ng) % umask_full, & & OCEAN(ng) % tl_u(:,:,:,nrhs(ng))) IF (FoundError(status, nf90_noerr, 724, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idUvel)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! ! Write out 3D V-momentum component (m/s). ! IF (Hout(idVvel,ng)) THEN scale=1.0_dp gtype=gfactor*v3dvar status=nf_fwrite3d(ng, iTLM, TLM(ng)%ncid, idVvel, & & TLM(ng)%Vid(idVvel), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, 1, N(ng), scale, & & GRID(ng) % vmask_full, & & OCEAN(ng) % tl_v(:,:,:,nrhs(ng))) IF (FoundError(status, nf90_noerr, 796, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idVvel)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! ! Write out tracer type variables. ! DO itrc=1,NT(ng) IF (Hout(idTvar(itrc),ng)) THEN scale=1.0_dp gtype=gfactor*r3dvar status=nf_fwrite3d(ng, iTLM, TLM(ng)%ncid, idTvar(itrc), & & TLM(ng)%Tid(itrc), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, 1, N(ng), scale, & & GRID(ng) % rmask, & & OCEAN(ng) % tl_t(:,:,:,nrhs(ng),itrc)) IF (FoundError(status, nf90_noerr, 869, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idTvar(itrc))), & & TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF END DO ! ! Write out density anomaly. ! IF (Hout(idDano,ng)) THEN scale=1.0_dp gtype=gfactor*r3dvar status=nf_fwrite3d(ng, iTLM, TLM(ng)%ncid, idDano, & & TLM(ng)%Vid(idDano), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, 1, N(ng), scale, & & GRID(ng) % rmask, & & OCEAN(ng) % tl_rho) IF (FoundError(status, nf90_noerr, 922, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idDano)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! ! Write out vertical viscosity coefficient. ! IF (Hout(idVvis,ng)) THEN scale=1.0_dp gtype=gfactor*w3dvar status=nf_fwrite3d(ng, iTLM, TLM(ng)%ncid, idVvis, & & TLM(ng)%Vid(idVvis), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, 0, N(ng), scale, & & GRID(ng) % rmask, & & MIXING(ng) % Akv, & & SetFillVal = .FALSE.) IF (FoundError(status, nf90_noerr, 954, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idVvis)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! ! Write out vertical diffusion coefficient for potential temperature. ! IF (Hout(idTdif,ng)) THEN scale=1.0_dp gtype=gfactor*w3dvar status=nf_fwrite3d(ng, iTLM, TLM(ng)%ncid, idTdif, & & TLM(ng)%Vid(idTdif), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, 0, N(ng), scale, & & GRID(ng) % rmask, & & MIXING(ng) % Akt(:,:,:,itemp), & & SetFillVal = .FALSE.) IF (FoundError(status, nf90_noerr, 982, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idTdif)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! ! Write out vertical diffusion coefficient for salinity. ! IF (Hout(idSdif,ng)) THEN scale=1.0_dp gtype=gfactor*w3dvar status=nf_fwrite3d(ng, iTLM, TLM(ng)%ncid, idSdif, & & TLM(ng)%Vid(idSdif), & & TLM(ng)%Rindex, gtype, & & LBi, UBi, LBj, UBj, 0, N(ng), scale, & & GRID(ng) % rmask, & & MIXING(ng) % Akt(:,:,:,isalt), & & SetFillVal = .FALSE.) IF (FoundError(status, nf90_noerr, 1012, MyFile)) THEN IF (Master) THEN WRITE (stdout,20) TRIM(Vname(1,idSdif)), TLM(ng)%Rindex END IF exit_flag=3 ioerror=status RETURN END IF END IF ! !----------------------------------------------------------------------- ! Synchronize tangent NetCDF file to disk to allow other processes ! to access data immediately after it is written. !----------------------------------------------------------------------- ! CALL netcdf_sync (ng, iTLM, TLM(ng)%name, TLM(ng)%ncid) IF (FoundError(exit_flag, NoError, 1140, MyFile)) RETURN ! 10 FORMAT (2x,'TL_WRT_HIS_NF90 - writing history', t42, & & 'fields (Index=',i1,',',i1,') in record = ',i0) 20 FORMAT (/,' TL_WRT_HIS_NF90 - error while writing variable: ',a, & & /,19x,'into tangent NetCDF file for time record: ',i0) ! RETURN END SUBROUTINE tl_wrt_his_nf90 END MODULE tl_wrt_his_mod