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 @ 154

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

CL + CT: BUGFIX099: Add missing "USE cpl_oce" and "USE geo2ocean" modules and syntax correction

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.1 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 , 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  :   Read wind stress from a coupled Atmospheric model
22      !!      - horizontal interpolation is done
23      !!        They are given in the geographic referential
24      !!      (zonal and meridional components at both U- and V-points)
25      !!     CAUTION: never mask the surface stress field !
26      !!
27      !! ** Action  :   update at each time-step the two components of the
28      !!      surface stress in both (i,j) and geographical referencial
29      !!
30      !! References : The OASIS User Guide, Version 2.0, CERFACS/TR 95/46
31      !!
32      !! History :
33      !!   7.0  !  94-03  (L. Terray)  Original code
34      !!        !  96-07  (Laurent TERRAY)  OASIS 2 Version
35      !!        !  96-11  (Eric Guilyardi) horizontal interpolation
36      !!        !  98-04  (M.A Foujols, S. Valcke, M. Imbard) OASIS2.2
37      !!   8.5  !  02-11  (G. Madec)  F90: Free form and module
38      !!----------------------------------------------------------------------
39      !! * Modules used
40      USE ioipsl                ! NetCDF library
41      USE cpl_oce               ! coupled ocean-atmosphere variables
42      USE geo2ocean             ! ???
43
44      !! * Arguments
45      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
46
47      !! * Local declarations
48      INTEGER :: ji,jj,jf
49      INTEGER :: itm1,isize,iflag,info,inuread,index
50!      INTEGER :: icpliter
51      REAL(wp), DIMENSION(jpidta,jpjdta) ::   &
52         ztaux , ztauxv,    &  ! ???
53         ztauy , ztauyu        !
54      REAL(wp), DIMENSION(jpi,jpj) ::   &
55         ztauxg, ztauyg        ! ???
56
57! Addition for SIPC CASE
58      CHARACTER (len=3) ::   clmodinf       ! Header or not
59!      CHARACTER (len=3) ::   cljobnam_r    ! Experiment name in the field brick, if any
60!      INTEGER ,DIMENSION(3) :: infos       ! infos in the field brick, if any
61      !!---------------------------------------------------------------------
62
63! 0. Initialization
64! -----------------
65
66      isize = jpiglo * jpjglo
67      itm1 = ( kt - nit000 + 1 ) - 1
68
69! 1. Reading wind stress from coupler
70! -----------------------------------
71
72      IF( MOD(kt,nexco) == 1 )THEN
73
74! Test what kind of message passing we are using
75
76          IF (cchan == 'PIPE') THEN
77
78! UNIT number for fields
79
80              inuread = 99
81
82! exchanges from to atmosphere=CPL to ocean
83
84              DO jf = 1, ntauc2o
85!                CALL PIPE_Model_Recv(cpl_readtau(jf), icpliter, numout)
86                OPEN (inuread, FILE=cpl_f_readtau(jf), FORM='UNFORMATTED')
87                IF( jf == 1 ) CALL locread( cpl_readtau(jf), ztaux , isize, inuread, iflag, numout )
88                IF( jf == 2 ) CALL locread( cpl_readtau(jf), ztauxv, isize, inuread, iflag, numout )
89                IF( jf == 3 ) CALL locread( cpl_readtau(jf), ztauy , isize, inuread, iflag, numout )
90                IF( jf == 4 ) CALL locread( cpl_readtau(jf), ztauyu, isize, inuread, iflag, numout )
91                CLOSE (inuread)
92              END DO
93
94          ELSE IF( cchan == 'SIPC' ) THEN
95
96!         Define IF a header must be encapsulated within the field brick :
97              clmodinf = 'NOT'   ! as $MODINFO in namcouple 
98!
99!         reading of input field zonal wind stress SOZOTAUX
100
101              index = 1
102!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztaux)
103
104!         reading of input field meridional wind stress SOZOTAU2 (at v point)
105
106              index = 2
107!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztaux2)
108
109!         reading of input field zonal wind stress SOMETAUY
110
111              index = 3
112!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztauy)
113
114!         reading of input field meridional wind stress SOMETAU2 (at u point)
115
116              index = 4
117!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztauy2)
118!
119
120          ELSE IF( cchan == 'CLIM' ) THEN
121!
122
123! exchanges from atmosphere=CPL to ocean
124
125              DO jf = 1, ntauc2o
126                IF (jf == 1) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztaux , info )
127                IF (jf == 2) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauxv, info )
128                IF (jf == 3) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauy , info )
129                IF (jf == 4) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauyu, info )
130                IF ( info /= CLIM_Ok) THEN
131                    WRITE(numout,*)'Pb in reading ', cpl_readtau(jf), jf
132                    WRITE(numout,*)'Couplage itm1 is = ',itm1
133                    WRITE(numout,*)'CLIM error code is = ', info
134                    WRITE(numout,*)'STOP in Fromcpl'
135                    STOP 'tau.coupled.h'
136                ENDIF
137              END DO
138
139          ENDIF
140
141! 2. CHANGING DATA GRID COORDINATES --> GLOBAL GRID COORDINATES
142! -------------------------------------------------------------
143
144          DO jj = 1, jpj
145            DO ji = 1, jpi
146              tauxg (ji,jj) = ztaux ( mig(ji), mjg(jj) )
147              tauyg (ji,jj) = ztauy ( mig(ji), mjg(jj) )
148              ztauxg(ji,jj) = ztauxv( mig(ji), mjg(jj) )
149              ztauyg(ji,jj) = ztauyu( mig(ji), mjg(jj) )
150            END DO
151          END DO
152
153          CALL repcmo( tauxg, ztauyg, ztauxg, tauyg, taux, tauy, kt )
154
155      ENDIF
156
157   END SUBROUTINE tau
Note: See TracBrowser for help on using the repository browser.