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.
trc_oce_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/trc_oce_tam.F90 @ 3612

Last change on this file since 3612 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: 4.8 KB
Line 
1MODULE trc_oce_tam
2#if defined key_tam
3   !!======================================================================
4   !!                      ***  MODULE  trc_oce_tam  ***
5   !! Ocean passive tracer  :  share SMS/Ocean variables
6   !!                          Tangent and Adjoint Module
7   !!======================================================================
8   !! History of the direct module:
9   !!   9.0  !  04-03  (C. Ethe)  F90: Free form and module
10   !! History of the T&A module:
11   !!   9.0  !  08-11  (A. Vidard)  original version
12   !!       NEMO 3.4  ! 2012-09 (A. Vidard) Deallocating and initialising options
13   !!----------------------------------------------------------------------
14   !!----------------------------------------------------------------------
15   !! Default option                         No Biological fluxes for light
16   !!----------------------------------------------------------------------
17   USE par_oce
18   USE dom_oce
19   USE lib_mpp
20   IMPLICIT NONE
21   !! * Module variables
22   REAL(wp), PUBLIC, SAVE, DIMENSION(:,:,:), ALLOCATABLE :: &
23      & etot3_tl, &
24      & etot3_ad
25   LOGICAL, PRIVATE, SAVE :: ll_alloctl = .FALSE., ll_allocad = .FALSE.
26   PUBLIC &
27      & trc_oce_alloc_tam,   &       !: Initialize the trend TAM fields
28      & trc_oce_dealloc_tam, &       !: Deallocate the trend TAM fields
29      & trc_oce_tam_init
30CONTAINS
31
32   INTEGER FUNCTION trc_oce_alloc_tam( kmode )
33      !!----------------------------------------------------------------------
34      !!                  ***  trc_oce_alloc_tam  ***
35      !!----------------------------------------------------------------------
36      INTEGER, optional :: kmode
37      INTEGER ::   ierr(2)        ! Local variables
38      INTEGER :: imode
39      !!----------------------------------------------------------------------
40      IF ( PRESENT(kmode) ) THEN
41         imode = kmode
42      ELSE
43         imode = 0
44      END IF
45      ierr(:) = 0
46      IF ( ( imode == 0 ) .OR. ( imode == 1 ) .AND. ( .NOT. ll_alloctl ) ) THEN
47      ALLOCATE( etot3_tl (jpi,jpj,jpk), STAT=ierr(1) )
48      ll_alloctl = .TRUE.
49      END IF
50      IF ( ( imode == 0 ) .OR. ( imode == 2 ) .AND. ( .NOT. ll_allocad ) ) THEN
51      ALLOCATE( etot3_ad (jpi,jpj,jpk), STAT=ierr(2) )
52      ll_allocad = .TRUE.
53      END IF
54      trc_oce_alloc_tam  = MAXVAL( ierr )
55      !
56      IF( trc_oce_alloc_tam /= 0 )   CALL ctl_warn('trc_oce_alloc: failed to allocate etot3 array')
57   END FUNCTION trc_oce_alloc_tam
58   !
59   INTEGER FUNCTION trc_oce_dealloc_tam( kmode )
60      !!----------------------------------------------------------------------
61      !!                  ***  trc_oce_dealloc_tam  ***
62      !!----------------------------------------------------------------------
63      INTEGER, optional :: kmode
64      INTEGER :: imode
65      INTEGER ::   ierr(2)        ! Local variables
66      !!----------------------------------------------------------------------
67      IF ( PRESENT(kmode) ) THEN
68         imode = kmode
69      ELSE
70         imode = 0
71      END IF
72      ierr(:) = 0
73      IF ( ( imode == 0 ) .OR. ( imode == 1 ) .AND. ( ll_alloctl ) ) THEN
74         DEALLOCATE( etot3_tl, STAT=ierr(1) )
75         ll_alloctl = .FALSE.
76      END IF
77      IF ( ( imode == 0 ) .OR. ( imode == 2 ) .AND. ( ll_allocad ) ) THEN
78         DEALLOCATE( etot3_ad, STAT=ierr(2) )
79         ll_allocad = .FALSE.
80      END IF
81      trc_oce_dealloc_tam  = MAXVAL( ierr )
82      !
83      IF( trc_oce_dealloc_tam /= 0 )   CALL ctl_warn('trc_oce_dealloc: failed to deallocate etot3 array')
84   END FUNCTION trc_oce_dealloc_tam
85   !
86   SUBROUTINE trc_oce_tam_init( kmode )
87      !!-----------------------------------------------------------------------
88      !!
89      !!                  ***  ROUTINE trc_oce_tam_init  ***
90      !!
91      !! ** Purpose : Allocate and initialize the tangent linear and
92      !!              adjoint arrays
93      !!
94      !! ** Method  : kindic = 0  allocate/initialize both tl and ad variables
95      !!              kindic = 1  allocate/initialize only tl variables
96      !!              kindic = 2  allocate/initialize only ad variables
97      !!
98      !! ** Action  :
99      !!
100      !! References :
101      !!
102      !! History :
103      !!        ! 2009-03 (A. Weaver) Initial version (based on oce_tam_init)
104      !!        ! 2010-04 (A. Vidard) Nemo3.2 update
105      !!        ! 2012-09 (A. Vidard) Nemo3.4 update
106      !!-----------------------------------------------------------------------
107      !! * Arguments
108      INTEGER :: kmode
109      INTEGER :: ierr
110      IF ( ( kmode == 0 ) .OR. ( kmode == 1 ) ) THEN
111         IF ( .NOT. ll_alloctl ) ierr = trc_oce_alloc_tam ( 1 )
112         etot3_tl(:,:,:) = 0.0_wp
113      END IF
114      IF ( ( kmode == 0 ) .OR. ( kmode == 2 ) ) THEN
115         IF ( .NOT. ll_allocad ) ierr = trc_oce_alloc_tam ( 2 )
116         etot3_ad(:,:,:) = 0.0_wp
117      END IF
118   END SUBROUTINE trc_oce_tam_init
119#endif
120END MODULE trc_oce_tam
121
Note: See TracBrowser for help on using the repository browser.