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.
tstool_tam.F90 in branches/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC – NEMO

source: branches/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC/tstool_tam.F90 @ 3611

Last change on this file since 3611 was 3611, checked in by pabouttier, 11 years ago

Add TAM code and ORCA2_TAM configuration - see Ticket #1007

  • Property svn:executable set to *
File size: 7.9 KB
Line 
1MODULE tstool_tam
2   !!==========================================================================
3   !!     ***  MODULE  tstool_tam : TAM testing utilities  ***
4   !!==========================================================================
5   !! History of the NEMOTAM module:
6   !!             3.0  !  08-11  (A. Vidard) initial version
7   USE par_oce,        ONLY: & ! Ocean space and time domain variables
8      & jpi,                 &
9      & jpj,                 &
10      & jpk,                 &
11      & jpiglo,              &
12      & jpjglo
13   USE dom_oce       , ONLY: & ! Ocean space and time domain
14      & e1u,                 &
15      & e2u,                 &
16#if defined key_zco
17      & e3t_0,               &
18#else
19      & e3u,                 &
20#endif
21      & umask,               &
22      & mig,                 &
23      & mjg,                 &
24      & nldi,                &
25      & nldj,                &
26      & nlei,                &
27      & nlej
28   USE wrk_nemo       ! Memory Allocation
29   USE par_kind      , ONLY: & ! Precision variables
30      & wp
31   USE in_out_manager, ONLY: & ! I/O manager
32      & lwp
33   USE gridrandom    , ONLY: & ! Random Gaussian noise on grids
34      & grid_random
35   USE dotprodfld    , ONLY: & ! Computes dot product for 3D and 2D fields
36      & dot_product
37   IMPLICIT NONE
38   PRIVATE
39   REAL(KIND=wp), PUBLIC ::  & ! random field standard deviation for:
40      & stdu   =  0.01_wp,    & !   u-velocity
41      & stdv   =  0.01_wp,    & !   v-velocity
42      & stdw   = 0.01_wp,    & !   w-velocity
43#if defined key_obc
44      & stds   = 0.001_wp,    & !   salinity
45      & stdt   = 0.020_wp,    & !   temperature
46      & stdssh = 0.005_wp,   & !   sea surface height
47#else
48      & stds   =  0.01_wp,    & !   salinity
49      & stdt   =  0.1_wp,    & !   temperature
50      & stdssh = 0.01_wp,    & !   sea surface height
51#endif
52      & stdemp = 0.001_wp,    & !   evaporation minus precip 0.1_wp / SQRT( wesp_emp )
53      & stdqns =  0.1_wp,    & !   non solar heat flux
54      & stdqsr =  0.1_wp,    & !   solar heat flux
55      & stdgc  =  0.01_wp,    & !   gcx, gcb
56      & stdr   =  0.01_wp,    & !   rotb, rhd
57      & stdh   =  0.01_wp       !   hdivb
58
59   PUBLIC &
60      & prntst_adj,          &
61      & prntst_tlm
62
63#  include "domzgr_substitute.h90"
64
65CONTAINS
66
67   SUBROUTINE prntst_adj( cd_name, kumadt, psp1, psp2 )
68      CHARACTER(LEN=14), INTENT(in) :: cd_name
69      REAL(wp), INTENT(in) :: psp1, psp2
70      INTEGER, INTENT(in) :: kumadt
71      REAL(KIND=wp) :: &
72         & zspdif,       & ! scalar product difference
73         & ztol            ! accepted tolerance
74      CHARACTER (LEN=47) :: &
75         & FMT
76      CHARACTER (LEN=9)  :: &
77         & cl_stat         ! Accuracy status of adjoint routine (ok or warning)
78
79      ! Compare the scalar products
80
81      zspdif = ABS( psp1 - psp2 )
82      IF ( psp1 /= 0.0_wp ) zspdif = zspdif / ABS( psp1 )
83
84      ztol = EPSILON( zspdif ) * 10.
85
86      IF ( zspdif < ztol ) THEN
87         cl_stat = '   ok    '
88      ELSEIF ( zspdif < ztol*1000._wp ) THEN
89         cl_stat = ' warning '
90      ELSE
91         cl_stat = 'RED ALERT'
92      ENDIF
93
94      IF (lwp) THEN
95         FMT = "(A14,1X,E20.15,2X,E20.15,2X,E6.1,1X,E6.1,1x,A9)"
96         WRITE(kumadt,FMT) cd_name, psp1, psp2, zspdif, ztol, cl_stat
97         CALL FLUSH( kumadt )
98      ENDIF
99   END SUBROUTINE prntst_adj
100
101   SUBROUTINE prntst_tlm( cd_name, kumadt, psp1, psp2 )
102      CHARACTER(LEN=14), INTENT(in) :: cd_name
103      REAL(wp), INTENT(in) :: psp1, psp2
104      INTEGER, INTENT(in) :: kumadt
105      REAL(KIND=wp) :: &
106         & zspratio       ! scalar product difference
107      CHARACTER (LEN=47) :: &
108         & FMT
109      CHARACTER (LEN=9)  :: &
110         & cl_stat         ! Accuracy status of adjoint routine (ok or warning)
111
112      ! Compare the scalar products
113
114      IF ( psp1 /= 0.0_wp ) zspratio = 100 * psp1 /  psp2
115
116      IF (lwp) THEN
117         FMT = "(A14,1X,E20.13,2X,E20.15,2X,E6.1,1X)"
118         WRITE(kumadt,FMT) cd_name, psp1, psp2, zspratio
119         CALL FLUSH( kumadt )
120      ENDIF
121   END SUBROUTINE prntst_tlm
122
123   SUBROUTINE example_adj_tst( kumadt )
124      !!-----------------------------------------------------------------------
125      !!
126      !!                  ***  ROUTINE example_adj_tst ***
127      !!
128      !! ** Purpose : Test the adjoint routine.
129      !!
130      !! ** Method  : Verify the scalar product
131      !!
132      !!                 ( L dx )^T W dy  =  dx^T L^T W dy
133      !!
134      !!              where  L   = tangent routine
135      !!                     L^T = adjoint routine
136      !!                     W   = diagonal matrix of scale factors
137      !!                     dx  = input perturbation (random field)
138      !!                     dy  = L dx
139      !!
140      !!
141      !! History :
142      !!        ! 08-08 (A. Vidard)
143      !!-----------------------------------------------------------------------
144      !! * Modules used
145
146      !! * Arguments
147      INTEGER, INTENT(IN) :: &
148         & kumadt             ! Output unit
149
150      !! * Local declarations
151      INTEGER ::  &
152         & ji,    &        ! dummy loop indices
153         & jj,    &
154         & jk
155      REAL(KIND=wp) :: &
156         & zsp1,         & ! scalar product involving the tangent routine
157         & zsp2            ! scalar product involving the adjoint routine
158      REAL(KIND=wp), POINTER, DIMENSION(:,:,:) :: &
159         & z_tlin ,     & ! Tangent input
160         & z_tlout,     & ! Tangent output
161         & z_adin ,     & ! Adjoint input
162         & z_adout,     & ! Adjoint output
163         & zr             ! 3D random field
164      CHARACTER(LEN=14) :: &
165         & cl_name
166      ! Allocate memory
167
168      CALL wrk_alloc( jpi, jpj, jpk, z_tlin , z_tlout, z_adin, z_adout, zr )
169
170      !==================================================================
171      ! 1) dx = ( un_tl, vn_tl, hdivn_tl ) and
172      !    dy = ( hdivb_tl, hdivn_tl )
173      !==================================================================
174
175      !--------------------------------------------------------------------
176      ! Reset the tangent and adjoint variables
177      !--------------------------------------------------------------------
178          z_tlin( :,:,:) = 0.0_wp
179          z_tlout(:,:,:) = 0.0_wp
180          z_adin( :,:,:) = 0.0_wp
181          z_adout(:,:,:) = 0.0_wp
182          zr(     :,:,:) = 0.0_wp
183      !--------------------------------------------------------------------
184      ! Initialize the tangent input with random noise: dx
185      !--------------------------------------------------------------------
186
187      CALL grid_random( zr, 'U', 0.0_wp, stdr )
188      z_tlin(:,:,:) = zr(:,:,:)
189
190      CALL example_tan
191      !--------------------------------------------------------------------
192      ! Initialize the adjoint variables: dy^* = W dy
193      !--------------------------------------------------------------------
194
195      DO jk = 1, jpk
196        DO jj = nldj, nlej
197           DO ji = nldi, nlei
198              z_adin(ji,jj,jk) = z_tlout(ji,jj,jk) &
199                 &               * e1u(ji,jj) * e2u(ji,jj) * fse3u(ji,jj,jk) &
200                 &               * umask(ji,jj,jk)
201            END DO
202         END DO
203      END DO
204      !--------------------------------------------------------------------
205      ! Compute the scalar product: ( L dx )^T W dy
206      !--------------------------------------------------------------------
207
208      zsp1 = DOT_PRODUCT( z_tlout, z_adin )
209
210      !--------------------------------------------------------------------
211      ! Call the adjoint routine: dx^* = L^T dy^*
212      !--------------------------------------------------------------------
213
214      CALL example_adj
215
216      zsp2 = DOT_PRODUCT( z_tlin, z_adout )
217
218      ! 14 char:'12345678901234'
219      cl_name = 'example_adj   '
220      CALL prntst_adj( cl_name, kumadt, zsp1, zsp2 )
221
222      CALL wrk_dealloc( jpi, jpj, jpk, z_tlin , z_tlout, z_adin, z_adout, zr )
223
224   END SUBROUTINE example_adj_tst
225
226   SUBROUTINE example_tan
227   END SUBROUTINE example_tan
228   SUBROUTINE example_adj
229   END SUBROUTINE example_adj
230
231END MODULE tstool_tam
Note: See TracBrowser for help on using the repository browser.