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.
trcdta.F90 in trunk/NEMO/TOP_SRC – NEMO

source: trunk/NEMO/TOP_SRC/trcdta.F90 @ 941

Last change on this file since 941 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.9 KB
Line 
1MODULE trcdta
2   !!======================================================================
3   !!                     ***  MODULE  trcdta  ***
4   !! Ocean data  :  reads passive tracer data
5   !!=====================================================================
6   !!  TOP 1.0,  LOCEAN-IPSL (2005)
7   !! $Header$
8   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
9   !!----------------------------------------------------------------------
10
11#if  defined key_passivetrc && defined key_dtatrc
12   !!----------------------------------------------------------------------
13   !!   'key_dtatrc'                           3D tracer data field
14   !!----------------------------------------------------------------------
15   !!   dta_trc      : read ocean passive tracer data
16   !!----------------------------------------------------------------------
17   !! * Modules used
18   USE oce_trc
19   USE trc
20   USE par_sms
21   USE lib_print
22
23   IMPLICIT NONE
24   PRIVATE
25
26   !! * Routine accessibility
27   PUBLIC dta_trc   ! called by trcdtr.F90 and trcdmp.F90
28
29   !! * Shared module variables
30   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk,jptra) ::   &  !:
31      trdta             !: tracer data at given time-step
32
33   !! * Module variables
34   REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,2) ::   &
35      tracdta            ! tracer data at two consecutive times
36   INTEGER , DIMENSION(jptra) :: &
37      nlectr  ,   &    !!: switch for reading once
38      ntrc1   ,   &    !!: number of first month when reading 12 monthly value
39      ntrc2            !!: number of second month when reading 12 monthly value
40
41   !! * Substitutions
42#  include "passivetrc_substitute.h90"
43
44   !!----------------------------------------------------------------------
45   !!   OPA 9.0 , LODYC-IPSL  (2003)
46   !!----------------------------------------------------------------------
47
48CONTAINS
49
50   !!----------------------------------------------------------------------
51   !!   Default case                                            NetCDF file
52   !!----------------------------------------------------------------------
53   
54   SUBROUTINE dta_trc( kt )
55      !!----------------------------------------------------------------------
56      !!                   ***  ROUTINE dta_trc  ***
57      !!
58      !! ** Purpose :   Reads passive tracer data (Levitus monthly data)
59      !!
60      !! ** Method  :   Read on unit numtr the interpolated tracer concentra-
61      !!      tion onto the global grid. Data begin at january.
62      !!      The value is centered at the middle of month.
63      !!      In the opa model, kt=1 agree with january 1.
64      !!      At each time step, a linear interpolation is applied between
65      !!      two monthly values.
66      !!
67      !! History :
68      !!   8.2  !  02-04  (O. Aumont)  Original code
69      !!   9.0  !  04-03  (C. Ethe)   
70      !!   9.0  !  05-03  (O. Aumont and A. El Moussaoui) F90
71      !!----------------------------------------------------------------------
72      !! * Modules used
73      USE iom
74
75      !! * Arguments
76      INTEGER, INTENT( in ) ::   kt     ! ocean time-step
77
78      !! * Local declarations
79      INTEGER :: ji, jj, jn, jl 
80      INTEGER, PARAMETER ::  &
81         jpmois  = 12        ! number of months
82
83      INTEGER ::   &
84         imois, iman, i15, ik  ! temporary integers
85      CHARACTER (len=39) :: clname(jptra)
86      REAL(wp) :: zxy, zl
87      !!----------------------------------------------------------------------
88
89      DO jn = 1, jptra
90
91         IF( lutini(jn) ) THEN
92
93            IF ( kt == nittrc000 ) THEN
94               !! 3D tracer data
95               IF(lwp)WRITE(numout,*)
96               IF(lwp)WRITE(numout,*) ' dta_trc: reading tracer' 
97               IF(lwp)WRITE(numout,*) ' data file ', jn, ctrcnm(jn)
98               IF(lwp)WRITE(numout,*)
99               nlectr(jn) = 0
100            ENDIF
101            ! Initialization
102            iman = jpmois
103            i15  = nday/16
104            imois = nmonth + i15 -1
105            IF( imois == 0 ) imois = iman
106
107
108            ! First call kt=nit000
109            ! --------------------
110
111            IF ( kt == nittrc000 .AND. nlectr(jn) == 0 ) THEN
112               ntrc1(jn) = 0
113               IF(lwp) WRITE(numout,*) ' trc_dta : Levitus tracer data monthly fields'
114               ! open file
115#if defined key_trc_pisces
116               clname(jn) = 'LEVITUS_'//ctrcnm(jn)
117#else
118               clname(jn) = ctrcnm(jn)
119#endif
120               CALL iom_open ( clname(jn), numtr(jn) )             
121
122            ENDIF
123
124#if defined key_trc_pisces
125            ! Read montly file
126            IF( ( kt == nittrc000 .AND. nlectr(jn) == 0)  .OR. imois /= ntrc1(jn) ) THEN
127               nlectr(jn) = 1
128
129               ! Calendar computation
130
131               ! ntrc1 number of the first file record used in the simulation
132               ! ntrc2 number of the last  file record
133
134               ntrc1(jn) = imois
135               ntrc2(jn) = ntrc1(jn) + 1
136               ntrc1(jn) = MOD( ntrc1(jn), iman )
137               IF ( ntrc1(jn) == 0 ) ntrc1(jn) = iman
138               ntrc2(jn) = MOD( ntrc2(jn), iman )
139               IF ( ntrc2(jn) == 0 ) ntrc2(jn) = iman
140               IF(lwp) WRITE(numout,*) 'first record file used ntrc1 ', ntrc1(jn) 
141               IF(lwp) WRITE(numout,*) 'last  record file used ntrc2 ', ntrc2(jn)
142
143               ! Read montly passive tracer data Levitus
144
145               CALL iom_get ( numtr(jn), jpdom_data, ctrcnm(jn), tracdta(:,:,:,jn,1), ntrc1(jn) )
146               CALL iom_get ( numtr(jn), jpdom_data, ctrcnm(jn), tracdta(:,:,:,jn,2), ntrc2(jn) )
147
148               IF(lwp) THEN
149                  WRITE(numout,*)
150                  WRITE(numout,*) ' read tracer data ', ctrcnm(jn),' ok'
151                  WRITE(numout,*)
152               ENDIF
153
154               ! Apply Mask
155               DO jl = 1, 2
156                  tracdta(:,:,:  ,jn,jl) = tracdta(:,:,:,jn,jl) * tmask(:,:,:) 
157                  tracdta(:,:,jpk,jn,jl) = 0.
158                  IF( ln_zps ) THEN                ! z-coord. with partial steps
159                     DO jj = 1, jpj                ! interpolation of temperature at the last level
160                        DO ji = 1, jpi
161                           ik = mbathy(ji,jj) - 1
162                           IF( ik > 2 ) THEN
163                              zl = ( gdept(ik) - fsdept(ji,jj,ik) ) / ( gdept(ik) - gdept(ik-1) )
164                              tracdta(ji,jj,ik,jn,jl) = (1.-zl) * tracdta(ji,jj,ik,jn,jl) + zl * tracdta(ji,jj,ik-1,jn,jl)
165                           ENDIF
166                        END DO
167                     END DO
168                  ENDIF
169
170               END DO
171
172            ENDIF
173
174            IF(lwp) THEN
175               WRITE(numout,*) ctrcnm(jn), 'Levitus month ', ntrc1(jn),   &
176                  ntrc2(jn)
177               WRITE(numout,*)
178               WRITE(numout,*) ' Levitus month = ', ntrc1(jn),   &
179                  '  level = 1'
180               CALL prihre( tracdta(1,1,1,jn,1), jpi, jpj, 1, jpi, 20, 1   &
181                  ,jpj, 20, 1., numout )
182               WRITE(numout,*) ' Levitus month = ', ntrc1(jn),    &
183                  '  level = ',jpk/2
184               CALL prihre( tracdta(1,1,jpk/2,jn,1), jpi, jpj, 1, jpi,    &
185                  20, 1, jpj, 20, 1., numout )
186               WRITE(numout,*) ' Levitus month = ',ntrc1(jn)     &
187                  ,'  level = ',jpkm1
188               CALL prihre( tracdta(1,1,jpkm1,jn,1), jpi, jpj, 1, jpi,     &
189                  20, 1, jpj, 20, 1., numout )
190            ENDIF
191
192            ! At every time step compute temperature data
193
194            zxy = FLOAT( nday + 15 - 30 * i15 ) / 30.
195            trdta(:,:,:,jn)=  ( 1. - zxy ) * tracdta(:,:,:,jn,1)    &
196               +       zxy   * tracdta(:,:,:,jn,2) 
197
198            IF( jn == jpno3) trdta(:,:,:,jn) = trdta(:,:,:,jn) * 7.6E-6
199            IF( jn == jpdic) trdta(:,:,:,jn) = trdta(:,:,:,jn) * 1.E-6
200            IF( jn == jptal) trdta(:,:,:,jn) = trdta(:,:,:,jn) * 1.E-6
201            IF( jn == jpoxy) trdta(:,:,:,jn) = trdta(:,:,:,jn) * 44.6E-6
202            IF( jn == jpsil) trdta(:,:,:,jn) = trdta(:,:,:,jn) * 1.E-6
203            IF( jn == jppo4) trdta(:,:,:,jn) = trdta(:,:,:,jn) * 122.E-6
204
205            ! Close the file
206            ! --------------
207           
208            IF( kt == nitend )   CALL iom_close ( numtr(jn) )
209
210#else
211            ! Read init file only
212            IF( kt == nittrc000  ) THEN
213               CALL iom_get ( numtr(jn), jpdom_data, ctrcnm(jn), trdta(:,:,:,jn), ntrc1(jn) )
214               trdta(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:)
215               CALL iom_close ( numtr(jn) )
216            ENDIF 
217#endif
218
219        ENDIF
220
221       END DO
222
223   END SUBROUTINE dta_trc
224
225#else
226
227   !!----------------------------------------------------------------------
228   !!   Default case                        NO 3D passive tracer data field
229   !!----------------------------------------------------------------------
230CONTAINS
231   SUBROUTINE dta_trc( kt )        ! Empty routine
232      WRITE(*,*) 'dta_trc: You should not have seen this print! error?', kt
233   END SUBROUTINE dta_trc
234
235#endif
236
237END MODULE trcdta
Note: See TracBrowser for help on using the repository browser.