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.
initrc.F90 in trunk/NEMO/TOP_SRC – NEMO

source: trunk/NEMO/TOP_SRC/initrc.F90 @ 838

Last change on this file since 838 was 793, checked in by ctlod, 16 years ago

add USE lib_mpp line for MPI compilation, see ticket:#50

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.8 KB
RevLine 
[259]1MODULE initrc
[335]2   !!================================================
[259]3   !!
4   !!                       *** MODULE initrc ***
5   !! Initialisation the tracer model
[335]6   !!================================================
7                                                                                                                           
8#if defined key_passivetrc
[274]9
[335]10   !!-------------------------------------------------------
[340]11   !!  TOP 1.0,  LOCEAN-IPSL (2005)
[719]12   !! $Header$
[340]13   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
[335]14   !!-------------------------------------------------------
[274]15
[335]16   !!--------------------------------------------------------------
17   !! * Modules used
18   !! ==============
19   USE oce_trc
20   USE trc
21   USE trcrst
22   USE trcctl
23   USE trclec
24   USE trcdtr
25   USE trcini
[345]26   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine)
[793]27   USE lib_mpp         ! distributed memory computing
[335]28   
29   IMPLICIT NONE
30   PRIVATE
31   
32   
[259]33   !! * Accessibility
34   PUBLIC ini_trc
[617]35
36    !! * Substitutions
37#  include "domzgr_substitute.h90"
38 
[259]39CONTAINS
[335]40   
41   SUBROUTINE ini_trc
42      !!---------------------------------------------------------------------
43      !!
44      !!                       ROUTINE ini_trc
45      !!                     ******************
46      !!
47      !!  PURPOSE :
48      !!  ---------
49      !!     initialize the tracer model
50      !!
51      !!   METHOD :
52      !!   -------
53      !!
54      !!
55      !!   History:
56      !!   -------
57      !!      original  : 91-03 ()
58      !!      additions : 92-01 (C. Levy)
[345]59      !!                  05-03 (O. Aumont and A. El Moussaoui) F90
60      !!                  05-10 (C. Ethe ) print control initialization
[335]61      !!----------------------------------------------------------------------
[259]62
[335]63      !!---------------------------------------------------------------------
64      !!  OPA.9, 03-2005
65      !!---------------------------------------------------------------------
[617]66      INTEGER :: ji, jj, jk, jn    !: dummy loop indices
[259]67
[335]68      !! 0.b PRINT the number of tracer
69      !! ------------------------------
[259]70
71      IF(lwp) WRITE(numout,*) ' '
72      IF(lwp) WRITE(numout,*) ' *** number of passive tracer jptra = ',jptra
73      IF(lwp) WRITE(numout,*) ' '
74
[335]75      ! 1. READ passive tracers namelists
76      ! ---------------------------------
[259]77
78      CALL trc_lec
79
[335]80      ! 2. control consistency between parameters, cpp key and namelists
81      ! ----------------------------------------------------------------
[259]82
83      CALL trc_ctl
84
[335]85      ! 3. computes some initializations
86      ! --------------------------------
[259]87
88      CALL trc_ini
89
[617]90 
91      ! 4. total volume of the ocean
92      !-----------------------------
[259]93
[617]94      areatot = 0.
95      DO jk = 1, jpk
96         DO jj = 1, jpj
97            DO ji = 1, jpi
98               areatot = areatot + tmask(ji,jj,jk) * tmask_i(ji,jj)  &
99#if defined key_off_degrad
100                  &                * facvol(ji,jj,jk)    &
101#endif
102                  &                * e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) 
103            END DO
104         END DO
105      END DO
106      IF( lk_mpp ) THEN
107         CALL mpp_sum(areatot)     ! sum over the global domain 
108      END IF
109
110      IF(lwp) WRITE(numout,*) ' '
111      IF (lwp) WRITE(numout,*) 'Total volume of ocean =',areatot
112      IF(lwp) WRITE(numout,*) ' '
113
114      ! 5. Initialization of tracers
115      ! -----------------------------
116
[335]117      IF( lrsttr ) THEN
[259]118
[617]119         ! 5.1 restart from a file
120         !------------------------
121         CALL trc_rst_read
[259]122
123      ELSE
124
[617]125         !  5.2 analytical formulation or global data
126         !-------------------------------------
[335]127         CALL trc_dtr
[259]128
129      ENDIF
130
[617]131
132      ! 6. Computation integral of all tracers
[345]133      !------------------
134
[617]135      trai = 0.
136      DO jn = 1, jptra
137         DO jk = 1, jpk
138            DO jj = 1, jpj
139               DO ji = 1, jpi
140                  trai = trai + trn(ji,jj,jk,jn) * tmask(ji,jj,jk) * tmask_i(ji,jj)    &
141#if defined key_off_degrad
142                     &              * facvol(ji,jj,jk)   &
143#endif
144
145                     &              * e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk)
146               END DO
147            END DO
148         END DO
149      ENDDO
150     
151      IF( lk_mpp ) THEN
152         CALL mpp_sum(trai)         ! sum over the global domain 
153      END IF
154
155      IF(lwp) WRITE(numout,*) ' '     
156      IF(lwp) WRITE(numout,*) 'Integral of all tracers over the full domain at initial time =',trai
157      IF(lwp) WRITE(numout,*) ' '
158
159      ! 6. Print control
160      !------------------
161
[345]162      IF( ln_ctl )    CALL prt_ctl_trc_init
163
[335]164   END SUBROUTINE ini_trc
[259]165
[617]166
[259]167#else
[335]168   !!======================================================================
169   !!  Empty module : No passive tracer
170   !!======================================================================
171CONTAINS
[617]172   SUBROUTINE ini_trc     
[335]173   END SUBROUTINE ini_trc
[259]174#endif
175
176END MODULE initrc 
Note: See TracBrowser for help on using the repository browser.