New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
tau_forced_monthly_fdir.h90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/tau_forced_monthly_fdir.h90 @ 3

Last change on this file since 3 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.8 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                ***  tau_forced_monthly_fdir.h90  ***
3   !!----------------------------------------------------------------------
4
5   !!----------------------------------------------------------------------
6   !!   tau     : update surface stress from monthly mean fields read in
7   !!             a direct access file
8   !!----------------------------------------------------------------------
9   !! * local modules variables
10   INTEGER ::           &
11      numtau = 64,      &  ! logical unit for the i-component of the wind data
12      ntau1, ntau2         ! index of the first and second record used
13   CHARACTER (len=32) ::   &
14      cl_tau = 'tauxy_1m'  &
15      !                    ! name of the monthly direct acces file
16      !                    ! which containt the 2 surface stress components
17   REAL(wp), DIMENSION(jpi,jpj,2,4) ::   &
18      taudta               ! the 2 components of the surface stress (Pascal)
19      !                    ! at 2 consecutive time-steps in the (i,j) referential
20   !!----------------------------------------------------------------------
21   !!   OPA 9.0 , LODYC-IPSL  (2003)
22   !!----------------------------------------------------------------------
23
24CONTAINS
25
26   SUBROUTINE tau( kt )
27      !!---------------------------------------------------------------------
28      !!                    ***  ROUTINE tau  ***
29      !!             
30      !! ** Purpose :   provide to the ocean the stress at each time step
31      !!
32      !! ** Method  : - Read the 2 monthly surface stress components in a
33      !!      direct access file at 2 consecutive time-steps
34      !!        They are given in the (i,j) referential
35      !!        The i-component is given at U-point (INTERP package)
36      !!        The j-component is given at V-point (INTERP package)
37      !!              - a linear time-interpolation is performed to provide
38      !!      the stress at the kt time-step.
39      !!
40      !!    CAUTION: never mask the surface stress field !
41      !!
42      !! ** Action :
43      !!        update at each time-step the two components of the surface
44      !!      stress in both (i,j) and geographical referencial
45      !!
46      !! History :
47      !!   4.0  !  91-03  (G. Madec)  Original code
48      !!   8.5  !  02-11  (G. Madec)  F90: Free form and module
49      !!----------------------------------------------------------------------
50      !! * Arguments
51      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
52
53      !! * Local declarations
54      INTEGER :: ji, jj, ios
55      INTEGER :: iimlu, ijmlu, ikmlu, ilmlu, immlu
56      INTEGER :: imois, iman
57      INTEGER :: i15
58      INTEGER :: ildta,ibloc,ilseq
59
60      CHARACTER (len=30) ::   cltit
61      CHARACTER (len=21) ::   clunf, clold, cldir
62
63      REAL(wp) ::   zxy, zfacto
64      REAL(wp), DIMENSION(jpi,jpj) ::   ztauxg, ztauyg
65!!---------------------------------------------------------------------
66
67
68! 0. Initialization
69! -----------------
70! Open specifier
71
72      clold = 'OLD'
73      clunf = 'UNFORMATTED'
74      cldir = 'DIRECT'
75
76      ilseq = 1
77
78! computation of the record length for direct access file
79! this length depend of 4096 (device specification)
80
81      ibloc = 4096
82      ildta = ibloc*((jpidta*jpjdta*jpbytda-1 )/ibloc+1)
83
84! iman=number of dates in data file (12 for a year of monthly values)
85      iman  = int(raamo)
86
87      i15 = INT( 2 * FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) )
88
89      imois = nmonth + i15 - 1
90      IF ( imois == 0 ) imois = iman
91
92
93! 1. first call kt=nit000
94! -----------------------
95
96      IF( kt == nit000 ) THEN
97          ntau1 = 0
98          IF(lwp) WRITE(numout,*) ' '
99          IF(lwp) WRITE(numout,*) ' tau    : monthly stress direct access file'
100          IF(lwp) WRITE(numout,*) ' ~~~~~~'
101          IF(lwp) WRITE(numout,*)
102          IF(lwp) WRITE(numout,*) 'file numtau = ', numtau
103
104! title, dimensions and tests
105
106          CALL ctlopn(numtau, cl_tau, clold, clunf, cldir, ildta, numout, lwp, 1 )
107          READ ( numtau, REC=1, IOSTAT=ios ) cltit, iimlu, ijmlu, ikmlu, ilmlu, immlu
108
109          IF(lwp) WRITE(numout,*)' number of points in the 5 directions '
110          IF(lwp) WRITE(numout,*) iimlu, ijmlu, ikmlu, ilmlu, immlu
111      ENDIF
112
113
114! 2. Read monthly file
115! -------------------
116
117      IF ( kt == nit000 .OR. imois /= ntau1 ) THEN
118
119! 2.1 calendar computation
120
121! ntau1 number of the first file record used in the simulation
122! ntau2 number of the last  file record
123
124          ntau1 = imois
125          ntau2 = ntau1+1
126          ntau1 = mod( ntau1, iman )
127          IF ( ntau1 == 0 ) ntau1 = iman
128          ntau2 = MOD( ntau2, iman )
129          IF ( ntau2 == 0 ) ntau2 = iman
130          IF(lwp) WRITE(numout,*) 'first record file used ntau1 ', ntau1
131          IF(lwp) WRITE(numout,*) 'last  record file used ntau2 ', ntau2
132
133! 2.3 Read monthly stress data Hellerman
134
135! ntau1
136! ...Txu
137          CALL read2D(numtau,taudta(1,1,1,1),1,6*(ntau1-1)+3)
138! ...Txv
139          CALL read2D(numtau,taudta(1,1,1,2),1,6*(ntau1-1)+4)
140! ...Tyu
141          CALL read2D(numtau,taudta(1,1,1,3),1,6*(ntau1-1)+6)
142! ...Tyv
143          CALL read2D(numtau,taudta(1,1,1,4),1,6*(ntau1-1)+7)
144! ntau2
145! ...Txu
146          CALL read2D(numtau,taudta(1,1,2,1),1,6*(ntau2-1)+3)
147! ...Txv
148          CALL read2D(numtau,taudta(1,1,2,2),1,6*(ntau2-1)+4)
149! ...Tyu
150          CALL read2D(numtau,taudta(1,1,2,3),1,6*(ntau2-1)+6)
151! ...Tyv
152          CALL read2D(numtau,taudta(1,1,2,4),1,6*(ntau2-1)+7)
153
154          IF(lwp) THEN
155          WRITE(numout,*) ' '
156          WRITE(numout,*) ' read Clio stress ok'
157          WRITE(numout,*) ' '
158          WRITE(numout,*) ' month: ', ntau1, '  field: 1 multiply by ', 1.
159          CALL prihre( taudta(1,1,1,1), jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout )
160          WRITE(numout,*) ' '
161          WRITE(numout,*) ' month: ', ntau2, '  field: 2 multiply by ', 1.
162          CALL prihre( taudta(1,1,2,4), jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout )
163          ENDIF
164
165      ENDIF
166
167 
168! 4. At every time step compute stress data
169! -----------------------------------------
170
171      zfacto     = 1.
172! zxy : coefficient for linear interpolation in time
173      zxy = FLOAT( nday ) / FLOAT( nobis(ntau1) ) + 0.5 - i15
174
175! ...Txu
176      tauxg (:,:) = zfacto * ( (1.-zxy) * taudta(:,:,1,1) + zxy * taudta(:,:,2,1) )
177! ...Tyu
178      tauyg (:,:) = zfacto * ( (1.-zxy) * taudta(:,:,1,3) + zxy * taudta(:,:,2,3) )
179! ...Txv
180      ztauxg(:,:) = zfacto * ( (1.-zxy) * taudta(:,:,1,2) + zxy * taudta(:,:,2,2) )
181! ...Tyv
182      ztauyg(:,:) = zfacto * ( (1.-zxy) * taudta(:,:,1,4) + zxy * taudta(:,:,2,4) )
183
184! 2.4 changing data grid coordinates --> global grid coordinates
185
186      CALL repcmo( tauxg, tauyg, ztauxg, ztauyg, taux, tauy, kt )
187
188! 2.5 Save components
189
190      tauxg(:,:) = taux(:,:)
191      tauyg(:,:) = tauy(:,:)
192
193      CALL FLUSH(numout)
194      GO TO 412
195 410  IF(lwp)WRITE(numout,*) 'e r r o r read numtau ', ios
196      nstop = nstop +1
197 412  CONTINUE
198
199   END SUBROUTINE tau
Note: See TracBrowser for help on using the repository browser.