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 @ 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: 5.9 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   !! * 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  :   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      !! * Arguments
42      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
43
44      !! * Local declarations
45      INTEGER :: ji,jj,jf
46      INTEGER :: itm1,isize,iflag,icpliter,info,inuread,index
47      REAL(wp), DIMENSION(jpidta,jpjdta) ::   &
48         ztaux , ztauxv,    &  ! ???
49         ztauy , ztauyu        !
50      REAL(wp), DIMENSION(jpi,jpj) ::   &
51         ztauxg, ztauyg        ! ???
52
53! Addition for SIPC CASE
54      CHARACTER (len=3) ::   clmodinf       ! Header or not
55      CHARACTER (len=3) ::   cljobnam_r    ! Experiment name in the field brick, if any
56      INTEGER ,DIMENSION(3) :: infos       ! infos in the field brick, if any
57      !!---------------------------------------------------------------------
58
59! 0. Initialization
60! -----------------
61
62      isize = jpiglo * jpjglo
63      itm1 = ( kt - nit000 + 1 ) - 1
64
65! 1. Reading wind stress from coupler
66! -----------------------------------
67
68      IF( MOD(kt,nexco) == 1 )THEN
69
70! Test what kind of message passing we are using
71
72          IF (cchan == 'PIPE') THEN
73
74! UNIT number for fields
75
76              inuread = 99
77
78! exchanges from to atmosphere=CPL to ocean
79
80              DO jf = 1, ntauc2o
81!                CALL PIPE_Model_Recv(cpl_readtau(jf), icpliter, numout)
82                OPEN (inuread, FILE=cpl_f_readtau(jf), FORM='UNFORMATTED')
83                IF( jf == 1 ) CALL locread( cpl_readtau(jf), ztaux , isize, inuread, iflag, numout )
84                IF( jf == 2 ) CALL locread( cpl_readtau(jf), ztauxv, isize, inuread, iflag, numout )
85                IF( jf == 3 ) CALL locread( cpl_readtau(jf), ztauy , isize, inuread, iflag, numout )
86                IF( jf == 4 ) CALL locread( cpl_readtau(jf), ztauyu, isize, inuread, iflag, numout )
87                CLOSE (inuread)
88              END DO
89
90          ELSE IF( cchan == 'SIPC' ) THEN
91
92!         Define IF a header must be encapsulated within the field brick :
93              clmodinf = 'NOT'   ! as $MODINFO in namcouple 
94!
95!         reading of input field zonal wind stress SOZOTAUX
96
97              index = 1
98!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztaux)
99
100!         reading of input field meridional wind stress SOZOTAU2 (at v point)
101
102              index = 2
103!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztaux2)
104
105!         reading of input field zonal wind stress SOMETAUY
106
107              index = 3
108!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztauy)
109
110!         reading of input field meridional wind stress SOMETAU2 (at u point)
111
112              index = 4
113!              CALL SIPC_Read_Model(index, isize, clmodinf, cljobnam_r, infos, ztauy2)
114!
115
116          ELSE IF( cchan == 'CLIM' ) THEN
117!
118
119! exchanges from atmosphere=CPL to ocean
120
121              DO jf = 1, ntauc2o
122                IF (jf == 1) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztaux , info )
123                IF (jf == 2) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauxv, info )
124                IF (jf == 3) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauy , info )
125                IF (jf == 4) CALL CLIM_Import ( cpl_readtau(jf), itm1, ztauyu, info )
126                IF ( info /= CLIM_Ok) THEN
127                    WRITE(numout,*)'Pb in reading ', cpl_readtau(jf), jf
128                    WRITE(numout,*)'Couplage itm1 is = ',itm1
129                    WRITE(numout,*)'CLIM error code is = ', info
130                    WRITE(numout,*)'STOP in Fromcpl'
131                    STOP 'tau.coupled.h'
132                ENDIF
133              END DO
134
135          ENDIF
136
137! 2. CHANGING DATA GRID COORDINATES --> GLOBAL GRID COORDINATES
138! -------------------------------------------------------------
139
140          DO jj = 1, jpj
141            DO ji = 1, jpi
142              tauxg (ji,jj) = ztaux ( mig(ji), mjg(jj) )
143              tauyg (ji,jj) = ztauy ( mig(ji), mjg(jj) )
144              ztauxg(ji,jj) = ztauxv( mig(ji), mjg(jj) )
145              ztauyg(ji,jj) = ztauyu( mig(ji), mjg(jj) )
146            END DO
147          END DO
148
149          CALL repcmo( tauxg, ztauyg, ztauxg, tauyg, taux, tauy, kt )
150
151      ENDIF
152
153   END SUBROUTINE flx
Note: See TracBrowser for help on using the repository browser.