!!---------------------------------------------------------------------- !! *** tau_forced_monthly.h90 *** !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! tau : update the surface wind stress - monthly fields in NetCDF !! file. !!---------------------------------------------------------------------- !! * local modules variables INTEGER :: & numtau, & ! logical unit for the i-component of the wind data numtav, & ! logical unit for the j-component of the wind data ntau1, ntau2 ! index of the first and second record used REAL(wp), DIMENSION(jpi,jpj,2) :: & taux_dta, & ! i- and j-components of the surface stress (Pascal) tauy_dta ! at 2 consecutive months in the (i,j) referential !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2005) !! $Id$ !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt !!---------------------------------------------------------------------- CONTAINS SUBROUTINE tau( kt ) !!--------------------------------------------------------------------- !! *** ROUTINE tau *** !! !! ** Purpose : provide to the ocean the stress at each time step !! !! ** Method : - Read the 2 monthly surface stress components in NetCDF !! file at 2 consecutive time-steps !! They are given in the (i,j) referential !! The i-component is given at U-point (INTERP package) !! The j-component is given at V-point (INTERP package) !! - a linear time-interpolation is performed to provide the !! stress at the kt time-step. !! !! CAUTION: never mask the surface stress field ! !! !! ** Action : !! update at each time-step the two components of the surface !! stress in both (i,j) and geographical referencial !! !! History : !! 4.0 ! 91-03 (G. Madec) Original code !! 6.0 ! 92-07 (M. Imbard) !! 8.1 ! 00-08 (D. Ludicone) adapted to ERS-NCEP !! 8.5 ! 02-11 (G. Madec) F90: Free form and module !! ! daily/monthly, forced/coupled form !!---------------------------------------------------------------------- !! * Modules used USE iom !! * Arguments INTEGER, INTENT( in ) :: kt ! ocean time step !! * Local declarations INTEGER :: imois, iman, i15 REAL(wp) :: zxy ! coefficient of the linear time interpolation !!--------------------------------------------------------------------- ! -------------- ! ! Initialization ! ! -------------- ! ! iman=number of dates in data file (12 for a year of monthly values) iman = INT( raamo ) i15 = INT( 2*FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) ) imois = nmonth + i15 - 1 IF( imois == 0 ) imois = iman ! -------------------- ! ! First call kt=nit000 ! ! -------------------- ! IF( kt == nit000 ) THEN ntau1 = 0 ! initialization IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) ' tau : MONTHLY climatological wind stress (NetCDF files)' ENDIF CALL iom_open ( 'taux_1m.nc', numtau ) CALL iom_open ( 'tauy_1m.nc', numtav ) ENDIF ! ----------------- ! ! Read monthly file ! ! ----------------- ! IF( kt == nit000 .OR. imois /= ntau1 ) THEN ! Calendar computation ntau1 = imois ! index of the first record ntau2 = ntau1 + 1 ! index of the last record ntau1 = MOD( ntau1, iman ) IF( ntau1 == 0 ) ntau1 = iman ntau2 = MOD( ntau2, iman ) IF( ntau2 == 0 ) ntau2 = iman IF(lwp) WRITE(numout,*) 'first month used ntau1 = ', ntau1 IF(lwp) WRITE(numout,*) 'last month used ntau2 = ', ntau2 ! Read the corresponding 2 monthly stress data ! ntau1 CALL iom_get ( numtau, jpdom_data, 'sozotaux', taux_dta(:,:,1), ntau1 ) CALL iom_get ( numtav, jpdom_data, 'sometauy', tauy_dta(:,:,1), ntau1 ) CALL iom_get ( numtau, jpdom_data, 'sozotaux', taux_dta(:,:,2), ntau2 ) CALL iom_get ( numtav, jpdom_data, 'sometauy', tauy_dta(:,:,2), ntau2 ) IF(lwp .AND. nitend-nit000 <= 100 ) THEN WRITE(numout,*) WRITE(numout,*) ' monthly stress read' WRITE(numout,*) WRITE(numout,*) ' month: ', ntau1, ' taux: 1 multiply by ', 1. CALL prihre( taux_dta(:,:,1), jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout ) WRITE(numout,*) WRITE(numout,*) ' month: ', ntau2, ' tauy: 2 multiply by ', 1. CALL prihre( tauy_dta(:,:,2), jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout ) ENDIF CALL FLUSH(numout) ENDIF ! ------------------------------- ! ! linear time interpolation at kt ! ! ------------------------------- ! ! zxy : coefficient for linear interpolation in time zxy = FLOAT( nday ) / FLOAT( nobis(ntau1) ) + 0.5 - i15 taux(:,:) = (1.-zxy) * taux_dta(:,:,1) + zxy * taux_dta(:,:,2) tauy(:,:) = (1.-zxy) * tauy_dta(:,:,1) + zxy * tauy_dta(:,:,2) ! ------------------- ! ! Last call kt=nitend ! ! ------------------- ! ! Closing of the 2 files (required in mpp) IF( kt == nitend ) THEN CALL iom_close(numtau) CALL iom_close(numtav) ENDIF END SUBROUTINE tau