1 | SUBROUTINE dtatem ( kt ) |
---|
2 | !!---------------------------------------------------------------------- |
---|
3 | !! *** ROUTINE dtatem *** |
---|
4 | !! |
---|
5 | !! ** Purpose : Reads temperature data (Levitus monthly data) |
---|
6 | !! |
---|
7 | !! ** Method : Read on unit numtdt the interpolated Levitus |
---|
8 | !! temperature onto the global grid. |
---|
9 | !! Data begin at january. |
---|
10 | !! The value is centered at the middle of month. |
---|
11 | !! In the opa model, kt=1 agree with january 1. |
---|
12 | !! At each time step, a linear interpolation is applied between |
---|
13 | !! two monthly values. |
---|
14 | !! Read on unit numtdt |
---|
15 | !! |
---|
16 | !! ** Action : |
---|
17 | !! define t_dta array at time-step kt |
---|
18 | !! |
---|
19 | !! References : |
---|
20 | !! Sydney Levitus, climatological atlas of the world ocean |
---|
21 | !! NOAA professional paper 13, december 1982 |
---|
22 | !! |
---|
23 | !! History : |
---|
24 | !! ! 91-03 () Original code |
---|
25 | !! ! 92-07 (M. Imbard) |
---|
26 | !! ! 99-10 (M.A. Foujols, M. Imbard) NetCDF FORMAT |
---|
27 | !! 8.5 ! 02-09 (G. Madec) F90: Free form and module |
---|
28 | !!---------------------------------------------------------------------- |
---|
29 | !! * Arguments |
---|
30 | INTEGER, INTENT( in ) :: kt ! ocean time-step |
---|
31 | |
---|
32 | !! * Local declarations |
---|
33 | INTEGER, PARAMETER :: jpmois=12, jpf=1 |
---|
34 | INTEGER :: ji, jj, jl, ios, ik |
---|
35 | INTEGER :: ibloc, ilindta |
---|
36 | INTEGER :: imois, iman |
---|
37 | INTEGER :: iimlu, ijmlu, ikmlu, ilmlu, immlu |
---|
38 | INTEGER :: i15 |
---|
39 | REAL(wp) :: zxy, zl |
---|
40 | CHARACTER (len=20) :: cltit |
---|
41 | !!---------------------------------------------------------------------- |
---|
42 | |
---|
43 | |
---|
44 | ! 0. Initialization |
---|
45 | ! ----------------- |
---|
46 | |
---|
47 | iman = jpmois |
---|
48 | i15 = nday/16 |
---|
49 | imois = nmonth + i15 - 1 |
---|
50 | IF( imois == 0 ) imois = iman |
---|
51 | |
---|
52 | |
---|
53 | ! 1. First call kt=nit000 |
---|
54 | ! ----------------------- |
---|
55 | |
---|
56 | IF( kt == nit000 .AND. nlecte == 0 ) THEN |
---|
57 | ! open temp.dta file |
---|
58 | ibloc = 4096 |
---|
59 | ilindta = ibloc*((jpidta*jpjdta*jpbytda-1 )/ibloc+1) |
---|
60 | CALL ctlopn(numtdt,'data_1m_potiential_temperature_nomask','OLD', 'UNFORMATTED', 'DIRECT', & |
---|
61 | ilindta,numout,lwp,1) |
---|
62 | ntem1 = 0 |
---|
63 | IF(lwp) WRITE(numout,*) |
---|
64 | IF(lwp) WRITE(numout,*) 'dta_tem : read monthly temperature in direct acces file' |
---|
65 | IF(lwp) WRITE(numout,*) '~~~~~~~' |
---|
66 | IF(lwp) WRITE(numout,*) |
---|
67 | |
---|
68 | ! 1.2 Read first records |
---|
69 | |
---|
70 | ! title, dimensions and tests |
---|
71 | |
---|
72 | READ( numtdt, REC=1, IOSTAT=ios ) cltit, iimlu, ijmlu, ikmlu, & |
---|
73 | ilmlu, immlu |
---|
74 | IF( ios /= 0 ) THEN |
---|
75 | IF(lwp) WRITE(numout,*) 'e r r o r read numtdt ', ios |
---|
76 | STOP 'dtatem' |
---|
77 | ELSE |
---|
78 | IF ( iimlu /= jpidta ) STOP 4050 |
---|
79 | IF ( ijmlu /= jpjdta ) STOP 4060 |
---|
80 | IF ( ikmlu /= jpk ) STOP 4070 |
---|
81 | IF ( ilmlu /= jpmois ) STOP 4080 |
---|
82 | IF ( immlu /= jpf ) STOP 4090 |
---|
83 | IF(lwp) WRITE(numout,*) 'nb of points in the 5 directions ' |
---|
84 | IF(lwp) WRITE(numout,*) iimlu, ijmlu, ikmlu, ilmlu, immlu |
---|
85 | ENDIF |
---|
86 | |
---|
87 | ENDIF |
---|
88 | |
---|
89 | |
---|
90 | ! 2. Read monthly file |
---|
91 | ! ------------------- |
---|
92 | |
---|
93 | IF( ( kt == nit000 .AND. nlecte == 0 ) .OR. imois /= ntem1 ) THEN |
---|
94 | nlecte = 1 |
---|
95 | |
---|
96 | ! 2.1 Calendar computation |
---|
97 | |
---|
98 | ntem1 = imois ! first file record used |
---|
99 | ntem2 = ntem1 + 1 ! last file record used |
---|
100 | ntem1 = MOD( ntem1, iman ) |
---|
101 | IF( ntem1 == 0 ) ntem1 = iman |
---|
102 | ntem2 = MOD( ntem2, iman ) |
---|
103 | IF( ntem2 == 0 ) ntem2 = iman |
---|
104 | IF(lwp) WRITE(numout,*) 'first record file used ntem1 ', ntem1 |
---|
105 | IF(lwp) WRITE(numout,*) 'last record file used ntem2 ', ntem2 |
---|
106 | |
---|
107 | ! 2.3 Read monthly temperature data Levitus |
---|
108 | |
---|
109 | CALL read3d( numtdt, temdta(1,1,1,1), ntem1+1 ) |
---|
110 | CALL read3d( numtdt, temdta(1,1,1,2), ntem2+1 ) |
---|
111 | |
---|
112 | IF(lwp) WRITE(numout,*) |
---|
113 | IF(lwp) WRITE(numout,*) ' read Levitus temperature ok' |
---|
114 | IF(lwp) WRITE(numout,*) |
---|
115 | |
---|
116 | ! 2.4 Masks |
---|
117 | |
---|
118 | DO jl = 1, 2 |
---|
119 | temdta(:,:,:,jl) = temdta(:,:,:,jl) * tmask(:,:,:) |
---|
120 | temdta(:,:,jpk,jl) = 0. |
---|
121 | IF( lk_zps ) THEN ! z-coord. with partial steps |
---|
122 | DO jj = 1, jpj ! interpolation of temperature at the last level |
---|
123 | DO ji = 1, jpi |
---|
124 | ik = mbathy(ji,jj) - 1 |
---|
125 | IF ( ik > 2 ) THEN |
---|
126 | zl = ( gdept(ik) - fsgdept(ji,jj,ik) ) / ( gdept(ik) - gdept(ik-1) ) |
---|
127 | temdta(ji,jj,ik,jl) = (1.-zl) * temdta(ji,jj,ik,jl) +zl * temdta(ji,jj,ik-1,jl |
---|
128 | ENDIF |
---|
129 | END DO |
---|
130 | END DO |
---|
131 | ENDIF |
---|
132 | END DO |
---|
133 | |
---|
134 | IF(lwp) THEN |
---|
135 | WRITE(numout,*) 'temperature Levitus month ', ntem1, ntem2 |
---|
136 | WRITE(numout,*) |
---|
137 | WRITE(numout,*) ' Levitus mounth = ', ntem1, ' level = 1' |
---|
138 | CALL prihre( temdta(1,1,1,1), jpi, jpj, 1, jpi, 20, 1, jpj, 20, 1., numout ) |
---|
139 | WRITE(numout,*) ' Levitus mounth = ', ntem1, ' level = ', jpk/2 |
---|
140 | CALL prihre( temdta(1,1,jpk/2,1), jpi, jpj, 1, jpi, 20, 1, jpj, 20, 1., numout ) |
---|
141 | WRITE(numout,*) ' Levitus mounth = ',ntem1,' level = ', jpkm1 |
---|
142 | CALL prihre( temdta(1,1,jpkm1,1), jpi, jpj, 1, jpi, 20, 1, jpj, 20, 1., numout ) |
---|
143 | ENDIF |
---|
144 | ENDIF |
---|
145 | |
---|
146 | |
---|
147 | ! 2. At every time step compute temperature data |
---|
148 | ! ---------------------------------------------- |
---|
149 | |
---|
150 | zxy = FLOAT( nday + 15 - 30 * i15 ) / 30. |
---|
151 | t_dta(:,:,:) = (1.-zxy) * temdta(:,:,:,1) + zxy * temdta(:,:,:,2) |
---|
152 | |
---|
153 | END SUBROUTINE dta_tem |
---|