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.
sbc_oce_tam.F90 in branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/SBC – NEMO

source: branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/SBC/sbc_oce_tam.F90 @ 1885

Last change on this file since 1885 was 1885, checked in by rblod, 14 years ago

add TAM sources

File size: 11.5 KB
Line 
1MODULE sbc_oce_tam
2   !!----------------------------------------------------------------------
3   !!    This software is governed by the CeCILL licence (Version 2)
4   !!----------------------------------------------------------------------
5#if defined key_tam
6   !!======================================================================
7   !!                       ***  MODULE  sbc_oce_tam  ***
8   !! Surface module :   variables defined in core memory
9   !!                    Tangent and Adjoint Module
10   !!======================================================================
11   !! History of the direct module:
12   !!            9.0   !  06-06  (G. Madec)  Original code
13   !! History of the TAM module:
14   !!            9.0   !  08-11  (A. Vidard)  Original code
15   !!            9.0   !  09-03  (A. Weaver)  Allocate/initialization routine
16   !!----------------------------------------------------------------------
17   USE par_kind, ONLY : &       ! Precision variables
18      & wp
19   USE par_oce, ONLY : &        ! Ocean space and time domain variables
20      & jpi,   &
21      & jpj
22
23   IMPLICIT NONE
24
25   !! * Routine accessibility
26   PRIVATE
27
28   PUBLIC &
29      & sbc_oce_tam_init, & !: Initialize the TAM fields
30   !!----------------------------------------------------------------------
31   !!              Ocean Surface Boundary Condition fields
32   !!----------------------------------------------------------------------
33      & utau_tl, & !: Tangent linear of sea surface i-stress (ocean referential)     [N/m2]
34      & vtau_tl, & !: Tangent linear of sea surface j-stress (ocean referential)     [N/m2]
35      & wndm_tl, & !: Tangent linear of wind speed module at T-point (=|U10m-Uoce|)  [m/s
36      & qns_tl,  & !: Tangent linear of sea heat flux: non solar                     [W/m2]
37      & qsr_tl,  & !: Tangent linear of sea heat flux:     solar                     [W/m2]
38      & emp_tl,  & !: Tangent linear of freshwater budget: volume flux               [Kg/m2/s]
39      & emps_tl, & !: Tangent linear of freshwater budget: concentration/dillution   [Kg/m2/s]
40      & fr_i_tl, & !: Tangent linear of ice fraction  (between 0 to 1)               -
41                   !
42      & utau_ad, & !: Adjoint of sea surface i-stress (ocean referential)     [N/m2]
43      & vtau_ad, & !: Adjoint of sea surface j-stress (ocean referential)     [N/m2]
44      & wndm_ad, & !: Adjoint of wind speed module at T-point (=|U10m-Uoce|)  [m/s]
45      & qns_ad,  & !: Adjoint of sea heat flux: non solar                     [W/m2
46      & qsr_ad,  & !: Adjoint of sea heat flux:     solar                     [W/m2]
47      & emp_ad,  & !: Adjoint of freshwater budget: volume flux               [Kg/m2/s]
48      & emps_ad, & !: Adjoint of freshwater budget: concentration/dillution   [Kg/m2/s]
49      & fr_i_ad, & !: Adjoint of ice fraction  (between 0 to 1)               -
50   !!----------------------------------------------------------------------
51   !!                     Sea Surface Mean fields
52   !!----------------------------------------------------------------------
53      & ssu_m_tl, & !: Tangent linear of mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
54      & ssv_m_tl, & !: Tangent linear of mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
55      & sst_m_tl, & !: Tangent linear of mean (nn_fsbc time-step) surface sea temperature     [Celsius]
56      & sss_m_tl, & !: Tangent linear of mean (nn_fsbc time-step) surface sea salinity            [psu]
57                    !
58      & ssu_m_ad, & !: Adjoint of mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
59      & ssv_m_ad, & !: Adjoint of mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
60      & sst_m_ad, & !: Adjoint of mean (nn_fsbc time-step) surface sea temperature     [Celsius]
61      & sss_m_ad    !: Adjoint of mean (nn_fsbc time-step) surface sea salinity            [psu]
62
63   !!----------------------------------------------------------------------
64   !!              Ocean Surface Boundary Condition fields
65   !!----------------------------------------------------------------------
66   REAL(wp),  DIMENSION(:,:), ALLOCATABLE :: &
67      & utau_tl, & !: Tangent linear of sea surface i-stress (ocean referential)     [N/m2]
68      & vtau_tl, & !: Tangent linear of sea surface j-stress (ocean referential)     [N/m2]
69      & wndm_tl, & !: Tangent linear of wind speed module at T-point (=|U10m-Uoce|)  [m/s
70      & qns_tl,  & !: Tangent linear of sea heat flux: non solar                     [W/m2]
71      & qsr_tl,  & !: Tangent linear of sea heat flux:     solar                     [W/m2]
72      & emp_tl,  & !: Tangent linear of freshwater budget: volume flux               [Kg/m2/s]
73      & emps_tl, & !: Tangent linear of freshwater budget: concentration/dillution   [Kg/m2/s]
74      & fr_i_tl    !: Tangent linear of ice fraction  (between 0 to 1)               -
75
76   REAL(wp),  DIMENSION(:,:), ALLOCATABLE :: &
77      & utau_ad, & !: Adjoint of sea surface i-stress (ocean referential)     [N/m2]
78      & vtau_ad, & !: Adjoint of sea surface j-stress (ocean referential)     [N/m2]
79      & wndm_ad, & !: Adjoint of wind speed module at T-point (=|U10m-Uoce|)  [m/s]
80      & qns_ad,  & !: Adjoint of sea heat flux: non solar                     [W/m2
81      & qsr_ad,  & !: Adjoint of sea heat flux:     solar                     [W/m2]
82      & emp_ad,  & !: Adjoint of freshwater budget: volume flux               [Kg/m2/s]
83      & emps_ad, & !: Adjoint of freshwater budget: concentration/dillution   [Kg/m2/s]
84      & fr_i_ad    !: Adjoint of ice fraction  (between 0 to 1)               -
85
86   !!----------------------------------------------------------------------
87   !!                     Sea Surface Mean fields
88   !!----------------------------------------------------------------------
89   REAL(wp),  DIMENSION(:,:), ALLOCATABLE :: &
90      & ssu_m_tl, & !: mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
91      & ssv_m_tl, & !: mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
92      & sst_m_tl, & !: mean (nn_fsbc time-step) surface sea temperature     [Celsius]
93      & sss_m_tl    !: mean (nn_fsbc time-step) surface sea salinity            [psu]
94                   
95   REAL(wp),  DIMENSION(:,:), ALLOCATABLE :: &
96      & ssu_m_ad, & !: mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
97      & ssv_m_ad, & !: mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
98      & sst_m_ad, & !: mean (nn_fsbc time-step) surface sea temperature     [Celsius]
99      & sss_m_ad    !: mean (nn_fsbc time-step) surface sea salinity            [psu]
100
101CONTAINS
102
103   SUBROUTINE sbc_oce_tam_init( kindic )
104      !!-----------------------------------------------------------------------
105      !!
106      !!                  ***  ROUTINE sbc_oce_tam_init  ***
107      !!
108      !! ** Purpose : Allocate and initialize the tangent linear and
109      !!              adjoint arrays
110      !!
111      !! ** Method  : kindic = 0  allocate/initialize both tl and ad variables
112      !!              kindic = 1  allocate/initialize only tl variables
113      !!              kindic = 2  allocate/initialize only ad variables
114      !!
115      !! ** Action  :
116      !!                   
117      !! References :
118      !!
119      !! History :
120      !!        ! 09-03 (A. Weaver) Initial version (based on oce_tam_init)
121      !!-----------------------------------------------------------------------
122      !! * Arguments
123      INTEGER, INTENT(IN) :: &
124         & kindic        ! indicate which variables to allocate/initialize
125
126      !! * Local declarations
127     
128      ! Allocate tangent linear variable arrays
129      ! ---------------------------------------
130     
131      IF ( kindic == 0 .OR. kindic == 1 ) THEN
132
133         IF ( .NOT. ALLOCATED(utau_tl) ) THEN
134
135            ALLOCATE( utau_tl(jpi,jpj) )
136           
137         ENDIF
138         IF ( .NOT. ALLOCATED(vtau_tl) ) THEN
139
140            ALLOCATE( vtau_tl(jpi,jpj) )
141           
142         ENDIF
143         IF ( .NOT. ALLOCATED(wndm_tl) ) THEN
144
145            ALLOCATE( wndm_tl(jpi,jpj) )
146           
147         ENDIF
148         IF ( .NOT. ALLOCATED(qns_tl) ) THEN
149
150            ALLOCATE( qns_tl(jpi,jpj) )
151           
152         ENDIF
153         IF ( .NOT. ALLOCATED(qsr_tl) ) THEN
154
155            ALLOCATE( qsr_tl(jpi,jpj) )
156           
157         ENDIF
158         IF ( .NOT. ALLOCATED(emp_tl) ) THEN
159
160            ALLOCATE( emp_tl(jpi,jpj) )
161           
162         ENDIF
163         IF ( .NOT. ALLOCATED(emps_tl) ) THEN
164
165            ALLOCATE( emps_tl(jpi,jpj) )
166           
167         ENDIF
168         IF ( .NOT. ALLOCATED(fr_i_tl) ) THEN
169
170            ALLOCATE( fr_i_tl(jpi,jpj) )
171           
172         ENDIF
173         IF ( .NOT. ALLOCATED(ssu_m_tl) ) THEN
174
175            ALLOCATE( ssu_m_tl(jpi,jpj) )
176           
177         ENDIF
178         IF ( .NOT. ALLOCATED(ssv_m_tl) ) THEN
179
180            ALLOCATE( ssv_m_tl(jpi,jpj) )
181           
182         ENDIF
183         IF ( .NOT. ALLOCATED(sst_m_tl) ) THEN
184
185            ALLOCATE( sst_m_tl(jpi,jpj) )
186           
187         ENDIF
188         IF ( .NOT. ALLOCATED(sss_m_tl) ) THEN
189
190            ALLOCATE( sss_m_tl(jpi,jpj) )
191           
192         ENDIF
193
194         ! Initialize tangent linear variable arrays to zero
195         ! -------------------------------------------------
196
197         utau_tl (:,:) = 0.0_wp
198         vtau_tl (:,:) = 0.0_wp
199         wndm_tl (:,:) = 0.0_wp
200         qns_tl  (:,:) = 0.0_wp
201         qsr_tl  (:,:) = 0.0_wp
202         emp_tl  (:,:) = 0.0_wp
203         emps_tl (:,:) = 0.0_wp
204         fr_i_tl (:,:) = 0.0_wp
205         ssu_m_tl(:,:) = 0.0_wp
206         ssv_m_tl(:,:) = 0.0_wp
207         sst_m_tl(:,:) = 0.0_wp
208         sss_m_tl(:,:) = 0.0_wp
209
210      ENDIF
211
212      IF ( kindic == 0 .OR. kindic == 2 ) THEN
213
214         ! Allocate adjoint variable arrays
215         ! --------------------------------
216     
217         IF ( .NOT. ALLOCATED(utau_ad) ) THEN
218
219            ALLOCATE( utau_ad(jpi,jpj) )
220           
221         ENDIF
222         IF ( .NOT. ALLOCATED(vtau_ad) ) THEN
223
224            ALLOCATE( vtau_ad(jpi,jpj) )
225           
226         ENDIF
227         IF ( .NOT. ALLOCATED(wndm_ad) ) THEN
228
229            ALLOCATE( wndm_ad(jpi,jpj) )
230           
231         ENDIF
232         IF ( .NOT. ALLOCATED(qns_ad) ) THEN
233
234            ALLOCATE( qns_ad(jpi,jpj) )
235           
236         ENDIF
237         IF ( .NOT. ALLOCATED(qsr_ad) ) THEN
238
239            ALLOCATE( qsr_ad(jpi,jpj) )
240           
241         ENDIF
242         IF ( .NOT. ALLOCATED(emp_ad) ) THEN
243
244            ALLOCATE( emp_ad(jpi,jpj) )
245           
246         ENDIF
247         IF ( .NOT. ALLOCATED(emps_ad) ) THEN
248
249            ALLOCATE( emps_ad(jpi,jpj) )
250           
251         ENDIF
252         IF ( .NOT. ALLOCATED(fr_i_ad) ) THEN
253
254            ALLOCATE( fr_i_ad(jpi,jpj) )
255           
256         ENDIF
257         IF ( .NOT. ALLOCATED(ssu_m_ad) ) THEN
258
259            ALLOCATE( ssu_m_ad(jpi,jpj) )
260           
261         ENDIF
262         IF ( .NOT. ALLOCATED(ssv_m_ad) ) THEN
263
264            ALLOCATE( ssv_m_ad(jpi,jpj) )
265           
266         ENDIF
267         IF ( .NOT. ALLOCATED(sst_m_ad) ) THEN
268
269            ALLOCATE( sst_m_ad(jpi,jpj) )
270           
271         ENDIF
272         IF ( .NOT. ALLOCATED(sss_m_ad) ) THEN
273
274            ALLOCATE( sss_m_ad(jpi,jpj) )
275           
276         ENDIF
277
278         ! Initialize adjoint variable arrays to zero
279         ! ------------------------------------------
280
281         utau_ad (:,:) = 0.0_wp
282         vtau_ad (:,:) = 0.0_wp
283         wndm_ad (:,:) = 0.0_wp
284         qns_ad  (:,:) = 0.0_wp
285         qsr_ad  (:,:) = 0.0_wp
286         emp_ad  (:,:) = 0.0_wp
287         emps_ad (:,:) = 0.0_wp
288         fr_i_ad (:,:) = 0.0_wp
289         ssu_m_ad(:,:) = 0.0_wp
290         ssv_m_ad(:,:) = 0.0_wp
291         sst_m_ad(:,:) = 0.0_wp
292         sss_m_ad(:,:) = 0.0_wp
293
294      ENDIF
295
296   END SUBROUTINE sbc_oce_tam_init
297#endif
298
299END MODULE sbc_oce_tam
Note: See TracBrowser for help on using the repository browser.