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

source: trunk/NEMO/OPA_SRC/SBC/tau_coupled.h90 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.2 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                     ***  tau_coupled.h90  ***
3   !!----------------------------------------------------------------------
4
5   !!----------------------------------------------------------------------
6   !!   tau     :   update the surface stress - coupled ocean-atmosphere
7   !!               case, without sea-ice
8   !!----------------------------------------------------------------------
9   !!----------------------------------------------------------------------
10   !!   OPA 9.0 , LOCEAN-IPSL (2005)
11   !! $Header$
12   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
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  :   Read wind stress from a coupled Atmospheric model
24      !!      - horizontal interpolation is done
25      !!        They are given in the geographic referential
26      !!      (zonal and meridional components at both U- and V-points)
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 referencial
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         ztaux , ztauxv,    &  ! ???
55         ztauy , ztauyu        !
56      REAL(wp), DIMENSION(jpi,jpj) ::   &
57         ztauxg, ztauyg        ! ???
58
59! Addition for SIPC CASE
60      CHARACTER (len=3) ::   clmodinf       ! Header or not
61!      CHARACTER (len=3) ::   cljobnam_r    ! Experiment name in the field brick, if any
62!      INTEGER ,DIMENSION(3) :: infos       ! infos in the field brick, if any
63      !!---------------------------------------------------------------------
64
65! 0. Initialization
66! -----------------
67
68      isize = jpiglo * jpjglo
69      itm1 = ( kt - nit000 + 1 ) - 1
70
71! 1. Reading wind stress from coupler
72! -----------------------------------
73
74      IF( MOD(kt,nexco) == 1 )THEN
75
76! Test what kind of message passing we are using
77
78          IF (cchan == 'PIPE') THEN
79
80! UNIT number for fields
81
82              inuread = 99
83
84! exchanges from to atmosphere=CPL to ocean
85
86              DO jf = 1, ntauc2o
87!                CALL PIPE_Model_Recv(cpl_readtau(jf), icpliter, numout)
88                OPEN (inuread, FILE=cpl_f_readtau(jf), FORM='UNFORMATTED')
89                IF( jf == 1 ) CALL locread( cpl_readtau(jf), ztaux , isize, inuread, iflag, numout )
90                IF( jf == 2 ) CALL locread( cpl_readtau(jf), ztauxv, isize, inuread, iflag, numout )
91                IF( jf == 3 ) CALL locread( cpl_readtau(jf), ztauy , isize, inuread, iflag, numout )
92                IF( jf == 4 ) CALL locread( cpl_readtau(jf), ztauyu, isize, inuread, iflag, numout )
93                CLOSE (inuread)
94              END DO
95
96          ELSE IF( cchan == 'SIPC' ) THEN
97
98!         Define IF a header must be encapsulated within the field brick :
99              clmodinf = 'NOT'   ! as $MODINFO in namcouple 
100!
101!         reading of input field zonal wind stress SOZOTAUX
102
103              index = 1
104!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztaux)
105
106!         reading of input field meridional wind stress SOZOTAU2 (at v point)
107
108              index = 2
109!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztaux2)
110
111!         reading of input field zonal wind stress SOMETAUY
112
113              index = 3
114!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztauy)
115
116!         reading of input field meridional wind stress SOMETAU2 (at u point)
117
118              index = 4
119!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztauy2)
120!
121
122          ELSE IF( cchan == 'CLIM' ) THEN
123!
124
125! exchanges from atmosphere=CPL to ocean
126
127              DO jf = 1, ntauc2o
128                IF (jf == 1) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztaux , info )
129                IF (jf == 2) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauxv, info )
130                IF (jf == 3) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauy , info )
131                IF (jf == 4) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauyu, info )
132                IF ( info /= CLIM_Ok) THEN
133                    WRITE(numout,*)'Pb in reading ', cpl_readtau(jf), jf
134                    WRITE(numout,*)'Couplage itm1 is = ',itm1
135                    WRITE(numout,*)'CLIM error code is = ', info
136                    WRITE(numout,*)'STOP in Fromcpl'
137                    STOP 'tau.coupled.h'
138                ENDIF
139              END DO
140
141          ENDIF
142
143! 2. CHANGING DATA GRID COORDINATES --> GLOBAL GRID COORDINATES
144! -------------------------------------------------------------
145
146          DO jj = 1, jpj
147            DO ji = 1, jpi
148              tauxg (ji,jj) = ztaux ( mig(ji), mjg(jj) )
149              tauyg (ji,jj) = ztauy ( mig(ji), mjg(jj) )
150              ztauxg(ji,jj) = ztauxv( mig(ji), mjg(jj) )
151              ztauyg(ji,jj) = ztauyu( mig(ji), mjg(jj) )
152            END DO
153          END DO
154
155          CALL repcmo( tauxg, ztauyg, ztauxg, tauyg, taux, tauy, kt )
156
157      ENDIF
158
159   END SUBROUTINE tau
Note: See TracBrowser for help on using the repository browser.