SUBROUTINE get_data (ng) ! !svn $Id: get_data.F 413 2009-12-07 19:06:32Z arango $ !================================================== Hernan G. Arango === ! Copyright (c) 2002-2009 The ROMS/TOMS Group ! ! Licensed under a MIT/X style license ! ! See License_ROMS.txt ! !======================================================================= ! ! ! This routine reads in forcing, climatology and assimilation data ! ! from input NetCDF files. If there is more than one time-record, ! ! data is loaded into global two-time record arrays. The actual ! ! interpolation is carried elsewhere. ! ! ! ! Currently, this routine is only executed in serial mode by the ! ! main thread. ! ! ! !======================================================================= ! USE mod_param USE mod_boundary USE mod_forces USE mod_grid USE mod_iounits USE mod_ncparam USE mod_scalars USE mod_sources USE mod_stepping ! implicit none ! ! Imported variable declarations. ! integer, intent(in) :: ng ! ! Local variable declarations. ! logical, dimension(3) :: update = & & (/ .FALSE., .FALSE., .FALSE. /) integer :: ILB, IUB, JLB, JUB integer :: LBi, UBi, LBj, UBj integer :: i ! ! Lower and upper bounds for nontiled boundary arrays. ! ILB=0 IUB=Im(ng)+1 JLB=0 JUB=Jm(ng)+1 ! ! Lower and upper bounds for tiled arrays. ! LBi=LBOUND(GRID(ng)%h,DIM=1) UBi=UBOUND(GRID(ng)%h,DIM=1) LBj=LBOUND(GRID(ng)%h,DIM=2) UBj=UBOUND(GRID(ng)%h,DIM=2) ! !----------------------------------------------------------------------- ! Turn on input data time wall clock. !----------------------------------------------------------------------- ! CALL wclock_on (ng, iNLM, 3) ! !======================================================================= ! Read in forcing data from FORCING NetCDF file. !======================================================================= ! ! !----------------------------------------------------------------------- ! Point Sources/Sinks time dependent data. !----------------------------------------------------------------------- ! ! ! Point Source/Sink vertically integrated mass transport. ! CALL get_ngfld (ng, iNLM, idRtra, ncFRCid(idRtra,ng), & & nFfiles(ng), FRCname(1,ng), update(1), & & 1, Nsrc(ng), 1, 2, 1, Nsrc(ng), 1, & & SOURCES(ng) % QbarG(1,1)) ! ! Tracer Sources/Sinks. ! DO i=1,NT(ng) IF (LtracerSrc(i,ng)) THEN CALL get_ngfld (ng, iNLM, idRtrc(i), ncFRCid(idRtrc(i),ng), & & nFfiles(ng), FRCname(1,ng), update(1), & & 1, Nsrc(ng), N(ng), 2, 1, Nsrc(ng), N(ng), & & SOURCES(ng) % TsrcG(1,1,1,i)) END IF END DO ! !----------------------------------------------------------------------- ! Surface wind components. !----------------------------------------------------------------------- ! CALL get_2dfld (ng, iNLM, idUair, ncFRCid(idUair,ng), & & nFfiles(ng), FRCname(1,ng), update(1), & & LBi, UBi, LBj, UBj, 2, 1, & & GRID(ng) % rmask(LBi,LBj), & & FORCES(ng) % UwindG(LBi,LBj,1)) CALL get_2dfld (ng , iNLM, idVair, ncFRCid(idVair,ng), & & nFfiles(ng), FRCname(1,ng), update(1), & & LBi, UBi, LBj, UBj, 2, 1, & & GRID(ng) % rmask(LBi,LBj), & & FORCES(ng) % VwindG(LBi,LBj,1)) ! !----------------------------------------------------------------------- ! Surface air pressure. !----------------------------------------------------------------------- ! CALL get_2dfld (ng, iNLM, idPair, ncFRCid(idPair,ng), & & nFfiles(ng), FRCname(1,ng), update(1), & & LBi, UBi, LBj, UBj, 2, 1, & & GRID(ng) % rmask(LBi,LBj), & & FORCES(ng) % PairG(LBi,LBj,1)) ! !----------------------------------------------------------------------- ! Cloud fraction. !----------------------------------------------------------------------- ! CALL get_2dfld (ng, iNLM, idCfra, ncFRCid(idCfra,ng), & & nFfiles(ng), FRCname(1,ng), update(1), & & LBi, UBi, LBj, UBj, 2, 1, & & GRID(ng) % rmask(LBi,LBj), & & FORCES(ng) % cloudG(LBi,LBj,1)) ! !----------------------------------------------------------------------- ! Surface air temperature. !----------------------------------------------------------------------- ! CALL get_2dfld (ng, iNLM, idTair, ncFRCid(idTair,ng), & & nFfiles(ng), FRCname(1,ng), update(1), & & LBi, UBi, LBj, UBj, 2, 1, & & GRID(ng) % rmask(LBi,LBj), & & FORCES(ng) % TairG(LBi,LBj,1)) ! !----------------------------------------------------------------------- ! Surface air humidity. !----------------------------------------------------------------------- ! CALL get_2dfld (ng, iNLM, idQair, ncFRCid(idQair,ng), & & nFfiles(ng), FRCname(1,ng), update(1), & & LBi, UBi, LBj, UBj, 2, 1, & & GRID(ng) % rmask(LBi,LBj), & & FORCES(ng) % HairG(LBi,LBj,1)) ! !----------------------------------------------------------------------- ! Turn off input data time wall clock. !----------------------------------------------------------------------- ! CALL wclock_off (ng, iNLM, 3) RETURN END SUBROUTINE get_data