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