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

source: branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/SOL/sol_oce_tam.F90 @ 2587

Last change on this file since 2587 was 2587, checked in by vidard, 13 years ago

refer to ticket #798

File size: 7.3 KB
Line 
1MODULE sol_oce_tam
2   !!----------------------------------------------------------------------
3   !!    This software is governed by the CeCILL licence (Version 2)
4   !!----------------------------------------------------------------------
5   !!======================================================================
6   !!                       ***  MODULE sol_oce_tam ***
7   !! NEMOVAR : variables controlling the solver for tangent and adjoint models
8   !!======================================================================
9   !! History of the direct module:
10   !!            9.0  !  02-11  (G. Madec)  F90: Free form and module
11   !! History of the TAM module:
12   !!            9.0  !  09-03  (A. Weaver) original version
13   !!----------------------------------------------------------------------
14   !! * Modules used
15   USE par_kind      , ONLY: & ! Precision variables
16      & wp
17   USE in_out_manager, ONLY: & ! I/O manager
18      & nit000,              &
19      & nitend
20   USE par_oce       , ONLY: & ! Ocean space and time domain variables
21      & jpi,                 &
22      & jpj,                 & 
23      & jpr2di,              &
24      & jpr2dj
25!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
26!!! AW: This is the maximum number of iterations used in the balance operator
27!!      for a different elliptic equation than the one used in TAM.
28!!      Not a good idea to use the same parameter for both.
29!!
30   USE tamctl        , ONLY: & ! NEMOVAR variables for controlling the run
31      & nmax_fs
32!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
33   USE sol_oce       , ONLY: &
34      & nmin
35#if defined key_dynspg_flt
36   USE solver        , ONLY: & ! Solver
37      & solver_init
38#endif
39   !! * Routine accessibility
40   
41   IMPLICIT NONE
42
43   !! * Accessibility
44   PUBLIC &
45      & sol_oce_tam_init, & !: routine called by nemovar.F90
46      & sol_oce_tam_deallocate, &
47                    !
48      & gcx_tl,   & !: Tangent of now solution of the elliptic equation
49      & gcxb_tl,  & !: Tangent of before solution of the elliptic equation
50      & gcb_tl,   & !: Tangent of 2nd member of barotropic linear system
51      & gcr_tl,   & !: Tangent of residual =b-a.x
52      & gcx_ad,   & !: Adjoint of solution of the elliptic equation
53      & gcxb_ad,  & !: Adjoint of before solution of the elliptic equation
54      & gcb_ad ,  & !: Adjoint of 2nd member of barotropic linear system
55      & nitsor
56   !! * Module variables
57   INTEGER, DIMENSION(:), ALLOCATABLE :: &
58      & nitsor      !: Number of SOR iterations
59
60   REAL(wp), DIMENSION(:,:), ALLOCATABLE :: & 
61      & gcx_tl,   & !: Tangent of now solution of the elliptic equation
62      & gcxb_tl,  & !: Tangent of before solution of the elliptic equation
63      & gcb_tl,   & !: Tangent of 2nd member of barotropic linear system
64      & gcr_tl,   & !: Tangent of residual =b-a.x
65      & gcx_ad,   & !: Adjoint of solution of the elliptic equation
66      & gcxb_ad,  & !: Adjoint of before solution of the elliptic equation
67      & gcb_ad      !: Adjoint of 2nd member of barotropic linear system
68
69CONTAINS
70
71   SUBROUTINE sol_oce_tam_init( kindic )
72      !!-----------------------------------------------------------------------
73      !!
74      !!                  ***  ROUTINE sol_oce_tam_init  ***
75      !!
76      !! ** Purpose :
77      !!
78      !! ** Method  : kindic = 0  allocate/initialize both tl and ad variables
79      !!                          and allocate/initialize solver
80      !!              kindic = 1  allocate/initialize only tl variables
81      !!              kindic = 2  allocate/initialize only ad variables
82      !!
83      !! ** Action  :
84      !!                   
85      !! References :
86      !!
87      !! History :
88      !!        ! 07-09 (K. Mogensen) Initial version
89      !!        ! 09-03 (A. Weaver) Allocate and intialization added
90      !!-----------------------------------------------------------------------
91      !! * Arguments
92      INTEGER, INTENT(IN) :: &
93         & kindic        ! indicate which variables to allocate/initialize
94
95#if defined key_dynspg_flt
96      IF ( kindic == 0 .OR. kindic == 1 ) THEN
97
98         IF ( kindic == 0 ) CALL solver_init( nit000 )
99
100         IF ( .NOT. ALLOCATED(nitsor) ) THEN
101
102            ALLOCATE( nitsor( nitend - nit000 + 1 ) )
103            nitsor(:) = nmin
104
105         ENDIF
106
107
108      ENDIF
109     
110      IF ( kindic == 0 .OR. kindic == 1 ) THEN
111
112         IF (.NOT. ALLOCATED(gcx_tl) ) THEN
113         
114            ALLOCATE( gcx_tl (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) )
115
116         ENDIF
117         IF (.NOT. ALLOCATED(gcxb_tl) ) THEN
118
119            ALLOCATE( gcxb_tl(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) )
120
121         ENDIF
122         IF (.NOT. ALLOCATED(gcb_tl) ) THEN
123
124            ALLOCATE( gcb_tl (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) )
125
126         ENDIF
127         IF (.NOT. ALLOCATED(gcr_tl) ) THEN
128
129            ALLOCATE( gcr_tl (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) )
130
131         ENDIF
132
133         ! Initialize tangent linear variables arrays to zero
134         ! --------------------------------------------------
135
136         gcx_tl (:,:) = 0.0_wp
137         gcxb_tl(:,:) = 0.0_wp
138         gcb_tl (:,:) = 0.0_wp
139         gcr_tl (:,:) = 0.0_wp
140
141      ENDIF
142
143      IF ( kindic == 0 .OR. kindic == 2 ) THEN
144
145         IF (.NOT. ALLOCATED(gcx_ad) ) THEN
146         
147            ALLOCATE( gcx_ad (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) )
148
149         ENDIF
150         IF (.NOT. ALLOCATED(gcxb_ad) ) THEN
151
152            ALLOCATE( gcxb_ad(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) )
153
154         ENDIF
155         IF (.NOT. ALLOCATED(gcb_ad) ) THEN
156 
157            ALLOCATE( gcb_ad (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) )
158
159         ENDIF
160
161         ! Initialize adjoint variables arrays to zero
162         ! -------------------------------------------
163
164         gcx_ad (:,:) = 0.0_wp
165         gcxb_ad(:,:) = 0.0_wp
166         gcb_ad (:,:) = 0.0_wp
167
168      ENDIF
169#endif
170   END SUBROUTINE sol_oce_tam_init
171   SUBROUTINE sol_oce_tam_deallocate(kindic)
172      !!-----------------------------------------------------------------------
173      !!
174      !!                  ***  ROUTINE sol_oce_tam_deallocate  ***
175      !!
176      !! ** Purpose :
177      !!
178      !! ** Method  : kindic = 0  deallocate both tl and ad variables
179      !!              kindic = 1  deallocate only tl variables
180      !!              kindic = 2  deallocate only ad variables
181      !!
182      !! ** Action  :
183      !!                   
184      !! References :
185      !!
186      !! History :
187      !!         ! 2010-06 (A. Vidard) Initial version
188      !!-----------------------------------------------------------------------
189      !! * Arguments
190      INTEGER, INTENT(IN) :: &
191         & kindic        ! indicate which variables to allocate/initialize
192#if defined key_dynspg_flt
193      IF ( kindic == 0 ) THEN
194         IF ( ALLOCATED(nitsor) )  DEALLOCATE( nitsor )
195      END IF
196
197      IF ( kindic == 0 .OR. kindic == 1 ) THEN
198
199         IF ( ALLOCATED(gcx_tl) )  DEALLOCATE( gcx_tl  )
200
201         IF ( ALLOCATED(gcxb_tl) ) DEALLOCATE( gcxb_tl )
202
203         IF ( ALLOCATED(gcb_tl) )  DEALLOCATE( gcb_tl  )
204
205         IF ( ALLOCATED(gcr_tl) )  DEALLOCATE( gcr_tl  )
206
207      ENDIF
208
209      IF ( kindic == 0 .OR. kindic == 2 ) THEN
210
211         IF ( ALLOCATED(gcx_ad) )  DEALLOCATE( gcx_ad  )
212
213         IF ( ALLOCATED(gcxb_ad) ) DEALLOCATE( gcxb_ad )
214
215         IF ( ALLOCATED(gcb_ad) )  DEALLOCATE( gcb_ad  )
216
217      ENDIF
218     
219#endif
220   END SUBROUTINE sol_oce_tam_deallocate
221END MODULE sol_oce_tam
Note: See TracBrowser for help on using the repository browser.