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_coupled_ice.h90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/tau_coupled_ice.h90 @ 155

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

CL + CT: BUGFIX100: Add missing "USE cpl_oce" and "USE geo2ocean" modules, syntax correction and remove sciobc initialization with tau[xy] arrays (the wind stress is transmitted to the ice through icestp.F90 module)

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.2 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                   ***  tau_coupled_ice.h90  ***
3   !!----------------------------------------------------------------------
4
5   !!----------------------------------------------------------------------
6   !!   tau     :   update the surface stress - coupled case with LIM
7   !!               sea-ice model
8   !!----------------------------------------------------------------------
9   !!----------------------------------------------------------------------
10   !!   OPA 9.0 , LODYC-IPSL  (2003)
11   !!----------------------------------------------------------------------
12
13CONTAINS
14
15   SUBROUTINE tau( kt )
16      !!---------------------------------------------------------------------
17      !!                    ***  ROUTINE tau  ***
18      !! 
19      !! ** Purpose :   provide to the ocean the stress at each time step
20      !!
21      !! ** Method  :   Coupled case with LIM sea-ice model
22      !!      Read wind stress from a coupled Atmospheric model
23      !!      - horizontal interpolation is done in OASIS
24      !!        They are given in the 3D referential
25      !!      (3 components at both U- and V-points)
26      !!
27      !!    CAUTION: never mask the surface stress field !
28      !!
29      !! ** Action  :   update at each time-step the two components of the
30      !!                surface stress in both (i,j) and geographical ref.
31      !!
32      !! References : The OASIS User Guide, Version 2.0, CERFACS/TR 95/46
33      !!
34      !! History :
35      !!   7.0  !  94-03  (L. Terray)  Original code
36      !!        !  96-07  (Laurent TERRAY)  OASIS 2 Version
37      !!        !  96-11  (Eric Guilyardi) horizontal interpolation
38      !!        !  98-04  (M.A Foujols, S. Valcke, M. Imbard) OASIS2.2
39      !!   8.5  !  02-11  (G. Madec)  F90: Free form and module
40      !!----------------------------------------------------------------------
41      !! * Modules used
42      USE ioipsl                ! NetCDF library
43      USE cpl_oce               ! coupled ocean-atmosphere variables
44      USE geo2ocean             ! ???
45
46      !! * Arguments
47      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
48
49      !! * Local declarations
50      INTEGER :: ji,jj,jf
51      INTEGER :: itm1,isize,iflag,info,inuread,index
52!      INTEGER :: icpliter
53      REAL(wp), DIMENSION(jpidta,jpjdta) ::   &
54         ztauxxu, ztauyyu, ztauzzu,   &  ! 3 components of the wind stress
55         ztauxxv, ztauyyv, ztauzzv       ! at U- and V-points
56      REAL(wp), DIMENSION(jpi,jpj) ::   &
57         ztauxx, ztauyy, ztauzz,      &  ! ???
58         ztauxg, ztauyg, ztauver         !
59
60! netcdf outputs
61
62      CHARACTER (len=80) ::   clcpltnam
63      INTEGER :: nhoridct, nidct
64      INTEGER ,DIMENSION(jpi*jpj) :: ndexct
65      SAVE nhoridct,nidct,ndexct
66      LOGICAL, SAVE :: lfirstt=.true.
67      REAL(wp) ::   zjulian
68
69! Addition for SIPC CASE
70      CHARACTER (len=3) ::   clmodinf      ! Header or not
71!      CHARACTER (len=3) ::   cljobnam_r    ! Experiment name in the field brick, if any
72!      INTEGER ,DIMENSION(3) ::  infos          ! infos in the field brick, if any
73!!---------------------------------------------------------------------
74
75! 0. Initialization
76!------------------
77
78      isize = jpiglo * jpjglo
79      itm1 = ( kt - nit000 + 1 ) - 1
80
81! initialisation for output
82
83      IF( lfirstt ) THEN
84          lfirstt = .FALSE.
85          ndexct(:) = 0
86          clcpltnam = "cpl_oce_tau"
87
88! Compute julian date from starting date of the run
89          CALL ymds2ju( nyear    , nmonth, nday , 0.e0  , zjulian )
90          CALL histbeg( clcpltnam, jpiglo, glamt, jpjglo, gphit,   &
91             1, jpiglo, 1, jpjglo, 0, zjulian, rdt, nhoridct, nidct)
92! no vertical axis
93          CALL histdef( nidct, 'taux'  , 'taux'  , "-", jpi, jpj, nhoridct,   &
94             1, 1, 1, -99, 32, "inst", rdt, rdt )
95          CALL histdef( nidct, 'tauy'  , 'tauy'  , "-", jpi, jpj, nhoridct,   &
96             1, 1, 1, -99, 32, "inst", rdt, rdt )
97          CALL histdef( nidct, 'tauxeu', 'tauxeu', "-", jpi, jpj, nhoridct,   &
98             1, 1, 1, -99, 32, "inst", rdt, rdt )
99          CALL histdef( nidct, 'tauynu', 'tauynu', "-", jpi, jpj, nhoridct,   &
100             1, 1, 1, -99, 32, "inst", rdt, rdt )
101          CALL histdef( nidct, 'tauzzu', 'tauzzu', "-", jpi, jpj, nhoridct,   &
102             1, 1, 1, -99, 32, "inst", rdt, rdt )
103          CALL histdef( nidct, 'tauxev', 'tauxev', "-", jpi, jpj, nhoridct,   &
104             1, 1, 1, -99, 32, "inst", rdt, rdt )
105          CALL histdef( nidct, 'tauynv', 'tauynv', "-", jpi, jpj, nhoridct,   &
106             1, 1, 1, -99, 32, "inst", rdt, rdt )
107          CALL histdef( nidct, 'tauzzv', 'tauzzv', "-", jpi, jpj, nhoridct,   &
108             1, 1, 1, -99, 32, "inst", rdt, rdt )
109
110          DO jf = 1, ntauc2o
111            CALL histdef( nidct, cpl_readtau(jf), cpl_readtau(jf),   &
112               "-", jpi, jpj, nhoridct,   &
113               1, 1, 1, -99, 32, "inst", rdt, rdt )
114          END DO
115
116          CALL histend(nidct)
117
118      ENDIF
119
120! 1. Reading wind stress from coupler
121! -----------------------------------
122
123      IF( MOD(kt,nexco) == 1 ) THEN
124
125! Test what kind of message passing we are using
126
127          IF( cchan == 'PIPE' ) THEN
128
129! UNIT number for fields
130
131              inuread = 99
132
133! exchanges from to atmosphere=CPL to ocean
134
135              DO jf = 1, ntauc2o
136!                CALL PIPE_Model_Recv(cpl_readtau(jf), icpliter, numout)
137                OPEN (inuread, FILE=cpl_f_readtau(jf), FORM='UNFORMATTED')
138                IF( jf == 1 ) CALL locread(cpl_readtau(jf), ztauxxu,isize,inuread,iflag,numout)
139                IF( jf == 2 ) CALL locread(cpl_readtau(jf), ztauyyu,isize,inuread,iflag,numout)
140                IF( jf == 3 ) CALL locread(cpl_readtau(jf), ztauzzu,isize,inuread,iflag,numout)
141                IF( jf == 4 ) CALL locread(cpl_readtau(jf), ztauxxv,isize,inuread,iflag,numout)
142                IF( jf == 5 ) CALL locread(cpl_readtau(jf), ztauyyv,isize,inuread,iflag,numout)
143                IF( jf == 6 ) CALL locread(cpl_readtau(jf), ztauyyv,isize,inuread,iflag,numout)
144                CLOSE ( inuread )
145              END DO
146
147          ELSE IF( cchan == 'SIPC' ) THEN
148
149!         Define IF a header must be encapsulated within the field brick :
150              clmodinf = 'NOT'   ! as $MODINFO in namcouple 
151!
152!         reading of input field zonal wind stress SOZOTAUX
153
154              index = 1
155!              CALL SIPC_Read_Model(index, isize, clmodinf,cljobnam_r, infos, ztaux)
156
157!         reading of input field meridional wind stress SOZOTAU2 (at v point)
158
159              index = 2
160!              CALL SIPC_Read_Model(index, isize, clmodinf,cljobnam_r, infos, ztaux2)
161
162!         reading of input field zonal wind stress SOMETAUY
163
164              index = 3
165!              CALL SIPC_Read_Model(index, isize, clmodinf,cljobnam_r, infos, ztauy)
166
167!         reading of input field meridional wind stress SOMETAU2 (at u point)
168
169              index = 4
170!              CALL SIPC_Read_Model(index, isize, clmodinf,cljobnam_r, infos, ztauy2)
171!
172
173          ELSE IF ( cchan == 'CLIM' ) THEN
174
175              WRITE (numout,*) 'Reading wind stress from coupler ', kt
176
177! exchanges from atmosphere=CPL to ocean
178
179              DO jf = 1, ntauc2o
180                IF( jf == 1 ) CALL CLIM_Import (cpl_readtau(jf), itm1,ztauxxu,info)
181                IF( jf == 2 ) CALL CLIM_Import (cpl_readtau(jf), itm1,ztauyyu,info)
182                IF( jf == 3 ) CALL CLIM_Import (cpl_readtau(jf), itm1,ztauzzu,info)
183                IF( jf == 4 ) CALL CLIM_Import (cpl_readtau(jf), itm1,ztauxxv,info)
184                IF( jf == 5 ) CALL CLIM_Import (cpl_readtau(jf), itm1,ztauyyv,info)
185                IF( jf == 6 ) CALL CLIM_Import (cpl_readtau(jf), itm1,ztauzzv,info)
186                IF( info /= CLIM_Ok) THEN
187                    WRITE(numout,*)'Pb in reading ', cpl_readtau(jf), jf
188                    WRITE(numout,*)'Couplage itm1 is = ',itm1
189                    WRITE(numout,*)'CLIM error code is = ', info
190                    WRITE(numout,*)'STOP in Fromcpl'
191                    STOP 'tau.coupled.h90'
192                ENDIF
193              END DO
194          ENDIF
195
196          DO jf = 1, ntauc2o
197            IF( jf == 1 ) CALL histwrite(nidct,cpl_readtau(jf), kt,ztauxxu,jpi*jpj,ndexct)
198            IF( jf == 2 ) CALL histwrite(nidct,cpl_readtau(jf), kt,ztauyyu,jpi*jpj,ndexct)
199            IF( jf == 3 ) CALL histwrite(nidct,cpl_readtau(jf), kt,ztauzzu,jpi*jpj,ndexct)
200            IF( jf == 4 ) CALL histwrite(nidct,cpl_readtau(jf), kt,ztauxxv,jpi*jpj,ndexct)
201            IF( jf == 5 ) CALL histwrite(nidct,cpl_readtau(jf), kt,ztauyyv,jpi*jpj,ndexct)
202            IF( jf == 6 ) CALL histwrite(nidct,cpl_readtau(jf), kt,ztauzzv,jpi*jpj,ndexct)
203          END DO
204
205          CALL histsync(nidct)
206
207! 2. CHANGING DATA GRID COORDINATES --> GLOBAL GRID COORDINATES
208! -------------------------------------------------------------
209! On u grid
210          DO jj = 1, jpj
211            DO ji = 1, jpi
212              ztauxx(ji,jj) = ztauxxu( mig(ji), mjg(jj) )
213              ztauyy(ji,jj) = ztauyyu( mig(ji), mjg(jj) )
214              ztauzz(ji,jj) = ztauzzu( mig(ji), mjg(jj) )
215            END DO
216          END DO
217
218          CALL geo2oce( ztauxx, ztauyy, ztauzz, 'u', glamu, gphiu, tauxg, ztauyg, ztauver )
219
220          CALL histwrite( nidct, 'tauxeu', kt , tauxg  , jpi*jpj, ndexct )
221          CALL histwrite( nidct, 'tauynu', kt , ztauyg , jpi*jpj, ndexct )
222          CALL histwrite( nidct, 'tauzzu', kt , ztauver, jpi*jpj, ndexct )
223
224! On v grid
225          DO jj = 1, jpj
226            DO ji = 1, jpi
227              ztauxx(ji,jj) = ztauxxv( mig(ji), mjg(jj) )
228              ztauyy(ji,jj) = ztauyyv( mig(ji), mjg(jj) )
229              ztauzz(ji,jj) = ztauzzv( mig(ji), mjg(jj) )
230            END DO
231          END DO
232
233          CALL geo2oce( ztauxx, ztauyy, ztauzz, 'v', glamv, gphiv, ztauxg, tauyg, ztauver )
234
235          CALL histwrite( nidct, 'tauxev', kt , ztauxg , jpi*jpj, ndexct )
236          CALL histwrite( nidct, 'tauynv', kt , tauyg  , jpi*jpj, ndexct )
237          CALL histwrite( nidct, 'tauzzv', kt , ztauver, jpi*jpj, ndexct )
238
239
240          CALL repcmo( tauxg, ztauyg, ztauxg, tauyg, taux, tauy, kt )
241
242! sortie des composantes de vents : tauxn tauye
243
244          CALL histwrite( nidct, 'taux', kt , taux, jpi*jpj, ndexct )
245          CALL histwrite( nidct, 'tauy', kt , tauy, jpi*jpj, ndexct )
246          CALL histsync( nidct )
247          IF( nitend-kt < nexco ) CALL histclo( nidct )
248
249      ENDIF
250
251   END SUBROUTINE tau
Note: See TracBrowser for help on using the repository browser.