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.F90 in branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC/trc.F90 @ 2819

Last change on this file since 2819 was 2819, checked in by cetlod, 13 years ago

Improvment of branch dev_r2787_LOCEAN3_TRA_TRP

  • Property svn:keywords set to Id
File size: 8.8 KB
Line 
1MODULE trc
2   !!======================================================================
3   !!                      ***  MODULE  trc  ***
4   !! Passive tracers   :  module for tracers defined
5   !!======================================================================
6   !! History :   OPA  !  1996-01  (M. Levy)  Original code
7   !!              -   !  1999-07  (M. Levy)  for LOBSTER1 or NPZD model
8   !!              -   !  2000-04  (O. Aumont, M.A. Foujols)  HAMOCC3 and P3ZD
9   !!   NEMO      1.0  !  2004-03  (C. Ethe)  Free form and module
10   !!----------------------------------------------------------------------
11#if defined key_top
12   !!----------------------------------------------------------------------
13   !!   'key_top'                                                TOP models
14   !!----------------------------------------------------------------------
15   USE par_oce
16   USE par_trc
17   
18   IMPLICIT NONE
19   PUBLIC
20
21   PUBLIC   trc_alloc   ! called by nemogcm.F90
22
23   !! parameters for the control of passive tracers
24   !! --------------------------------------------------
25   INTEGER, PUBLIC                                                 ::   numnat        !: the number of the passive tracer NAMELIST
26
27   !! passive tracers fields (before,now,after)
28   !! --------------------------------------------------
29   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)               ::  trai           !: initial total tracer
30   REAL(wp), PUBLIC                                                ::  areatot        !: total volume
31   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  cvol           !: volume correction -degrad option-
32   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trn            !: traceur concentration for now time step
33   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  tra            !: traceur concentration for next time step
34   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trb            !: traceur concentration for before time step
35
36   !! interpolated gradient
37   !!-------------------------------------------------- 
38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtru           !: hor. gradient at u-points at bottom ocean level
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtrv           !: hor. gradient at v-points at bottom ocean level
40   
41   !! passive tracers  (input and output)
42   !! ------------------------------------------ 
43   LOGICAL             , PUBLIC                                    ::  ln_rsttr       !: boolean term for restart i/o for passive tracers (namelist)
44   LOGICAL             , PUBLIC                                    ::  lrst_trc       !: logical to control the trc restart write
45   INTEGER             , PUBLIC                                    ::  nn_dttrc       !: frequency of step on passive tracers
46   INTEGER             , PUBLIC                                    ::  nn_writetrc    !: time step frequency for concentration outputs (namelist)
47   INTEGER             , PUBLIC                                    ::  nutwrs         !: output FILE for passive tracers restart
48   INTEGER             , PUBLIC                                    ::  nutrst         !: logical unit for restart FILE for passive tracers
49   INTEGER             , PUBLIC                                    ::  nn_rsttr       !: control of the time step ( 0 or 1 ) for pass. tr.
50   CHARACTER(len = 80) , PUBLIC                                    ::  cn_trcrst_in   !: suffix of pass. tracer restart name (input)
51   CHARACTER(len = 80) , PUBLIC                                    ::  cn_trcrst_out  !: suffix of pass. tracer restart name (output)
52   REAL(wp)            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::  rdttrc         !: vertical profile of passive tracer time step
53   LOGICAL             , PUBLIC                                    ::  ln_trcdta      !: Read inputs data from files
54   LOGICAL             , PUBLIC                                    ::  ln_trcdmp      !: internal damping flag
55
56   !! information for outputs
57   !! --------------------------------------------------
58   TYPE, PUBLIC :: PTRACER                                                            !: Passive tracer type
59       CHARACTER(len = 20)  :: clsname  !: short name
60       CHARACTER(len = 80)  :: cllname  !: long name
61       CHARACTER(len = 20)  :: clunit   !: unit
62       LOGICAL              :: llinit   !: read in a file or not
63       LOGICAL              :: llsave   !: save the tracer or not
64   END TYPE PTRACER
65   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcnm         !: tracer name
66   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcln         !: trccer field long name
67   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcun         !: tracer unit
68   LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_ini     !: Initialisation from data input file
69   LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_wri     !: save the tracer or not
70
71   TYPE, PUBLIC :: DIAG                                                               !: passive trcacer ddditional diagnostic type
72      CHARACTER(len = 20)  :: sname    !: short name
73      CHARACTER(len = 80)  :: lname    !: long name
74      CHARACTER(len = 20)  :: units    !: unit
75   END TYPE DIAG
76
77   !! additional 2D/3D outputs namelist
78   !! --------------------------------------------------
79   REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,  :) ::   trc2d         !: additional 2d outputs array
80   REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc3d         !: additional 3d outputs array
81   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2d        !: 2d field short name
82   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2l        !: 2d field long name
83   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2u        !: 2d field unit
84   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3d        !: 3d field short name
85   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3l        !: 3d field long name
86   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3u        !: 3d field unit
87   LOGICAL            , PUBLIC                                        ::  ln_diatrc      !: boolean term for additional diagnostic
88   INTEGER            , PUBLIC                                        ::  nn_writedia    !: frequency of additional outputs
89
90   !! Biological trends
91   !! -----------------
92   LOGICAL            , PUBLIC                                        ::  ln_diabio      !: boolean term for biological diagnostic
93   INTEGER            , PUBLIC                                        ::  nn_writebio    !: frequency of biological outputs
94   REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  trbio          !: biological trends
95   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbio         !: bio field short name
96   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbil         !: bio field long name
97   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbiu         !: bio field unit
98
99   !!----------------------------------------------------------------------
100   !! NEMO/TOP 3.3.1 , NEMO Consortium (2010)
101   !! $Id$
102   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
103   !!----------------------------------------------------------------------
104CONTAINS
105
106   INTEGER FUNCTION trc_alloc()
107      !!-------------------------------------------------------------------
108      !!                    *** ROUTINE trc_alloc ***
109      !!-------------------------------------------------------------------
110      USE lib_mpp, ONLY: ctl_warn
111      !!-------------------------------------------------------------------
112      !
113      ALLOCATE( trn(jpi,jpj,jpk,jptra), trb(jpi,jpj,jpk,jptra), tra(jpi,jpj,jpk,jptra),       & 
114         &      gtru(jpi,jpj,jpk)     , gtrv(jpi,jpj,jpk)                             ,       &
115         &      cvol(jpi,jpj,jpk)     , rdttrc(jpk)           , trai(jptra)           ,       &
116         &      ctrcnm(jptra)         , ctrcln(jptra)         , ctrcun(jptra)         ,       & 
117         &      ln_trc_ini(jptra)     , ln_trc_wri(jptra)                             ,  STAT = trc_alloc  ) 
118
119      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays')
120      !
121   END FUNCTION trc_alloc
122
123#else
124   !!----------------------------------------------------------------------
125   !!  Empty module :                                     No passive tracer
126   !!----------------------------------------------------------------------
127#endif
128
129   !!======================================================================
130END MODULE trc
Note: See TracBrowser for help on using the repository browser.