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

source: trunk/NEMO/OPA_SRC/SBC/tau_forced_daily.h90 @ 114

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

CT : UPDATE073 : Correction of typo and control tests just after the flinopen CALL

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 6.9 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                   ***  tau_forced_daily.h90  ***
3   !!----------------------------------------------------------------------
4
5   !!----------------------------------------------------------------------
6   !!   tau     :   update the surface stress - daily fields in NetCDF file
7   !!----------------------------------------------------------------------
8   !! * local modules variables
9   INTEGER ::   &
10      numtau,         &  ! logical unit for the i-component of the wind data
11      numtav,         &  ! logical unit for the j-component of the wind data
12      ntau1, ntau2 ,  &  ! index of the first and second record used
13      ndaytau            ! new day for ers/ncep tau forcing
14
15   CHARACTER (len=34) ::   &      !!! * monthly climatology/interanual fields
16      cl_taux = 'taux.nc',  & ! generic name of the i-component monthly NetCDF file
17      cl_tauy = 'tauy.nc'     ! generic name of the j-component monthly NetCDF file
18   !!----------------------------------------------------------------------
19   !!   OPA 9.0 , LODYC-IPSL  (2003)
20   !!----------------------------------------------------------------------
21
22CONTAINS
23
24   SUBROUTINE tau( kt )
25      !!---------------------------------------------------------------------
26      !!                    ***  ROUTINE tau  ***
27      !!     
28      !! ** Purpose :   provide to the ocean the stress at each time step
29      !!
30      !! ** Method  :   Read the daily surface stress components in NetCDF
31      !!      file. They are given in the (i,j) referential
32      !!        The i-component is given at U-point (INTERP package)
33      !!        The j-component is given at V-point (INTERP package)
34      !!
35      !!    CAUTION: never mask the surface stress field !
36      !!
37      !! ** Action  :   update at each time-step the two components of the
38      !!      surface stress in both (i,j) and geographical referencial
39      !!
40      !! History :
41      !!   4.0  !  91-03  (G. Madec)  Original code
42      !!   6.0  !  92-07  (M. Imbard)
43      !!   8.1  !  00-08  (D. Ludicone) adapted to ERS-NCEP
44      !!   8.5  !  02-11  (G. Madec)  F90: Free form and module
45      !!        !  03-07  (C. Ethe, G. Madec)  daily generic forcing
46      !!----------------------------------------------------------------------
47      !! * Modules used
48      USE ioipsl       ! NetCDF library
49
50      !! * Arguments
51      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
52
53      !! * Local declarations
54      INTEGER, PARAMETER ::   jpday = 365
55      INTEGER ::   &
56         itime,   &
57         iday, idy,   &
58         ipi, ipj, ipk
59      INTEGER  , DIMENSION(jpday)  ::   istep
60      REAL(wp) , DIMENSION(jpi,jpj)::  &
61         zlon  , &
62         zlat
63      REAL(wp) , DIMENSION(jpk)::  &
64         zlev
65      REAL(wp) ::   zsecond, zdate0
66      !!---------------------------------------------------------------------
67
68      ! -------------- !
69      ! Initialization !
70      ! -------------- !
71
72      itime = jpday
73      ipi   = jpiglo
74      ipj   = jpjglo
75      ipk   = jpk
76      idy   = 365
77      IF ( nleapy == 1 ) idy = 366
78
79
80      ! -------------------- !
81      ! First call kt=nit000 !
82      ! -------------------- !
83
84      IF( kt == nit000 ) THEN
85         IF(lwp) THEN
86            WRITE(numout,*) ' '
87            WRITE(numout,*) ' tau    : DAILY wind stress in NetCDF files'
88            WRITE(numout,*) ' ~~~~~~~'
89         ENDIF
90         ! title, dimensions and tests
91         
92         CALL flinopen( cl_taux, mig(1), nlci, mjg(1), nlcj,   &   ! taux on U-grid
93                        .FALSE., ipi   , ipj, ipk   ,        &
94                        zlon , zlat  , zlev   , itime,       &
95                        istep, zdate0, zsecond, numtau )
96         
97         IF( itime /= jpday .AND. itime /= jpday+1 ) THEN
98            IF(lwp) WRITE(numout,cform_err)
99            IF(lwp) WRITE(numout,*) '   problem with time coordinates in file ', cl_taux
100            IF(lwp) WRITE(numout,*) '   itime = ', itime,' jpday = ',jpday
101            nstop = nstop + 1
102         ENDIF
103         IF( ipi /= jpidta .OR. ipj /= jpjdta  ) THEN
104            IF(lwp) WRITE(numout,cform_err)
105            IF(lwp) WRITE(numout,*) '   problem with size read in file ', cl_taux
106            IF(lwp) WRITE(numout,*) '   ipi = ',ipi,' jpidta = ',jpidta
107            IF(lwp) WRITE(numout,*) '   ipj = ',ipj,' jpjdta = ',jpjdta
108            nstop = nstop + 1
109         ENDIF
110
111         CALL flinopen( cl_tauy, mig(1), nlci, mjg(1), nlcj,   &   ! tauy on V-grid
112                        .FALSE., ipi   , ipj, ipk   ,        &
113                        zlon , zlat  , zlev   , itime,       &
114                        istep, zdate0, zsecond, numtav )
115         
116         IF( itime /= jpday .AND. itime /= jpday+1 ) THEN
117            IF(lwp) WRITE(numout,cform_err)
118            IF(lwp) WRITE(numout,*) '   problem with time coordinates in file ', cl_tauy
119            IF(lwp) WRITE(numout,*) '   itime = ', itime,' jpday = ',jpday
120            nstop = nstop + 1
121         ENDIF
122         IF( ipi /= jpidta .OR. ipj /= jpjdta ) THEN
123            IF(lwp) WRITE(numout,cform_err)
124            IF(lwp) WRITE(numout,*) '   problem with size read in file ', cl_tauy
125            IF(lwp) WRITE(numout,*) '   ipi = ',ipi,' jpidta = ',jpidta
126            IF(lwp) WRITE(numout,*) '   ipj = ',ipj,' jpjdta = ',jpjdta
127            nstop = nstop + 1
128         ENDIF
129      ENDIF
130
131      ! ----------------- !
132      ! Read daily file   !
133      ! ----------------- !
134
135      IF ( ndaytau /= nday ) THEN
136           
137         ndaytau = nday
138         iday  = nday_year
139           
140         ! Read daily wind stress data
141         CALL flinget( numtau,'taux',                 &   ! taux: i-component at U-pt
142                       jpidta,jpjdta,1,jpday,iday,    &
143                       iday,mig(1),nlci,mjg(1),nlcj,taux(1:nlci,1:nlcj) )
144         CALL flinget( numtav,'tauy',                 &   ! tauy: j-component at V-pt
145                       jpidta,jpjdta,1,jpday,iday,    &
146                       iday,mig(1),nlci,mjg(1),nlcj,tauy(1:nlci,1:nlcj) )
147           
148         IF (lwp .AND. nitend-nit000 <= 100 ) THEN
149            WRITE(numout,*)
150            WRITE(numout,*) ' read daily wind stress ok'
151            WRITE(numout,*)
152            WRITE(numout,*) ' day: ', ndastp , '  taux: 1 multiply by ', 1.
153            CALL prihre( taux, jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout )
154            WRITE(numout,*)
155            WRITE(numout,*) ' day: ', ndastp , '  tauy: 1 multiply by ', 1.
156            CALL prihre( tauy, jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout )
157            WRITE(numout,*) ' '
158         ENDIF
159           
160         CALL FLUSH(numout)
161      ENDIF
162         
163      ! Save components in geographical ref on U grid
164      tauxg(:,:) = taux(:,:)
165      tauyg(:,:) = tauy(:,:)
166         
167      ! ------------------- !
168      ! Last call kt=nitend !
169      ! ------------------- !
170
171      ! Closing of the 2 files
172      IF( kt == nitend ) THEN
173          CALL flinclo( numtau )
174          CALL flinclo( numtav )
175      ENDIF
176         
177   END SUBROUTINE tau
Note: See TracBrowser for help on using the repository browser.