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 NEMO/trunk/src/TOP – NEMO

source: NEMO/trunk/src/TOP/trc.F90 @ 12396

Last change on this file since 12396 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 11.3 KB
RevLine 
[186]1MODULE trc
2   !!======================================================================
3   !!                      ***  MODULE  trc  ***
4   !! Passive tracers   :  module for tracers defined
5   !!======================================================================
[2528]6   !! History :   OPA  !  1996-01  (M. Levy)  Original code
[945]7   !!              -   !  2000-04  (O. Aumont, M.A. Foujols)  HAMOCC3 and P3ZD
[2528]8   !!   NEMO      1.0  !  2004-03  (C. Ethe)  Free form and module
[186]9   !!----------------------------------------------------------------------
10   USE par_oce
11   USE par_trc
[8665]12   USE bdy_oce, only: jp_bdy, ln_bdy, nb_bdy, OBC_DATA
[945]13   
[186]14   IMPLICIT NONE
15   PUBLIC
16
[2715]17   PUBLIC   trc_alloc   ! called by nemogcm.F90
18
[9019]19   !                                     !!- logical units of passive tracers
20   INTEGER, PUBLIC ::   numont     = -1   !: reference passive tracer namelist output output.namelist.top
21   INTEGER, PUBLIC ::   numonr     = -1   !: reference passive tracer namelist output output.namelist.top
22   INTEGER, PUBLIC ::   numstr            !: tracer statistics
23   INTEGER, PUBLIC ::   numrtr            !: trc restart (read )
24   INTEGER, PUBLIC ::   numrtw            !: trc restart ( write )
[12377]25   CHARACTER(:), ALLOCATABLE, PUBLIC ::   numnat_ref   !: character buffer for reference passive tracer namelist_top_ref
26   CHARACTER(:), ALLOCATABLE, PUBLIC ::   numnat_cfg   !: character buffer for configuration specific passive tracer namelist_top_cfg
27   CHARACTER(:), ALLOCATABLE, PUBLIC ::   numtrc_ref   !: character buffer for reference passive tracer namelist_trc_ref
28   CHARACTER(:), ALLOCATABLE, PUBLIC ::   numtrc_cfg   !: character buffer for configuration specific passive tracer namelist_trc_cfg
[186]29
30   !! passive tracers fields (before,now,after)
31   !! --------------------------------------------------
[9019]32   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  trai           !: initial total tracer
33   REAL(wp), PUBLIC                                        ::  areatot        !: total volume
34   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  cvol           !: volume correction -degrad option-
[12377]35   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:,:) ::  tr           !: tracer concentration
[9019]36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  sbc_trc_b      !: Before sbc fluxes for tracers
37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  sbc_trc        !: Now sbc fluxes for tracers
[186]38
[9019]39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  trc_i          !: prescribed tracer concentration in sea ice for SBC
40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  trc_o          !: prescribed tracer concentration in ocean for SBC
41   INTEGER             , PUBLIC                            ::  nn_ice_tr      !: handling of sea ice tracers
[5385]42
[2528]43   !! interpolated gradient
44   !!-------------------------------------------------- 
[9019]45   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  gtru           !: hor. gradient at u-points at bottom ocean level
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  gtrv           !: hor. gradient at v-points at bottom ocean level
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  gtrui          !: hor. gradient at u-points at top    ocean level
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  gtrvi          !: hor. gradient at v-points at top    ocean level
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  qsr_mean        !: daily mean qsr
[186]50   
[3294]51   !! passive tracers  (input and output)
[945]52   !! ------------------------------------------ 
[9019]53   LOGICAL             , PUBLIC ::   ln_rsttr           !: boolean term for restart i/o for passive tracers (namelist)
54   LOGICAL             , PUBLIC ::   lrst_trc           !: logical to control the trc restart write
55   INTEGER             , PUBLIC ::   nn_writetrc        !: time step frequency for concentration outputs (namelist)
56   INTEGER             , PUBLIC ::   nutwrs             !: output FILE for passive tracers restart
57   INTEGER             , PUBLIC ::   nutrst             !: logical unit for restart FILE for passive tracers
58   INTEGER             , PUBLIC ::   nn_rsttr           !: control of the time step ( 0 or 1 ) for pass. tr.
59   CHARACTER(len = 80) , PUBLIC ::   cn_trcrst_in       !: suffix of pass. tracer restart name (input)
60   CHARACTER(len = 256), PUBLIC ::   cn_trcrst_indir    !: restart input directory
61   CHARACTER(len = 80) , PUBLIC ::   cn_trcrst_out      !: suffix of pass. tracer restart name (output)
62   CHARACTER(len = 256), PUBLIC ::   cn_trcrst_outdir   !: restart output directory
63   REAL(wp)            , PUBLIC ::   rdttrc             !: passive tracer time step
64   REAL(wp)            , PUBLIC ::   r2dttrc            !: = 2*rdttrc except at nit000 (=rdttrc) if neuler=0
65   LOGICAL             , PUBLIC ::   ln_top_euler       !: boolean term for euler integration
66   LOGICAL             , PUBLIC ::   ln_trcdta          !: Read inputs data from files
[12377]67   LOGICAL             , PUBLIC ::   ln_trcbc           !: Enable surface, lateral or open boundaries conditions
[9019]68   LOGICAL             , PUBLIC ::   ln_trcdmp          !: internal damping flag
69   LOGICAL             , PUBLIC ::   ln_trcdmp_clo      !: internal damping flag on closed seas
70   INTEGER             , PUBLIC ::   nittrc000          !: first time step of passive tracers model
71   LOGICAL             , PUBLIC ::   l_trcdm2dc         !: Diurnal cycle for TOP
[3294]72
[5385]73   !! Information for the ice module for tracers
74   !! ------------------------------------------
[9019]75   TYPE, PUBLIC ::   TRC_I_NML         !: Ice tracer namelist structure
76         REAL(wp)         :: trc_ratio    ! ice-ocean trc ratio
77         REAL(wp)         :: trc_prescr   ! prescribed ice trc cc
78         CHARACTER(len=2) :: ctrc_o       ! choice of ocean trc cc
[5385]79   END TYPE
[9019]80   !
81   REAL(wp)        , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   trc_ice_ratio    !: ice-ocean tracer ratio
82   REAL(wp)        , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   trc_ice_prescr   !: prescribed ice trc cc
83   CHARACTER(len=2), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   cn_trc_o         !: choice of ocean tracer cc
[5385]84
85
[186]86   !! information for outputs
87   !! --------------------------------------------------
[9019]88   TYPE, PUBLIC ::   PTRACER        !: Passive tracer type
89      CHARACTER(len=20) ::   clsname   ! short name
90      CHARACTER(len=80) ::   cllname   ! long name
91      CHARACTER(len=20) ::   clunit    ! unit
92      LOGICAL           ::   llinit    ! read in a file or not
93      LOGICAL           ::   llsbc     ! read in a file or not
94      LOGICAL           ::   llcbc     ! read in a file or not
95      LOGICAL           ::   llobc     ! read in a file or not
[3294]96   END TYPE PTRACER
[9019]97   !
98   CHARACTER(len=20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ctrcnm   !: tracer name
99   CHARACTER(len=80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ctrcln   !: trccer field long name
100   CHARACTER(len=20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ctrcun   !: tracer unit
101   !
102   TYPE, PUBLIC ::   DIAG         !: Passive trcacer ddditional diagnostic type
103      CHARACTER(len=20) ::   sname   ! short name
104      CHARACTER(len=80) ::   lname   ! long name
105      CHARACTER(len=20) ::   units   ! unit
[3294]106   END TYPE DIAG
[9019]107   !
108   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc3d   !: 3D diagnostics for tracers
109   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc2d   !: 2D diagnostics for tracers
[3294]110
[3680]111   !! information for inputs
112   !! --------------------------------------------------
[9019]113   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ln_trc_ini    !: Initialisation from data input file
114   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ln_trc_obc    !: Use open boundary condition data
115   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ln_trc_sbc    !: Use surface boundary condition data
116   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ln_trc_cbc    !: Use coastal boundary condition data
117   LOGICAL , PUBLIC                                  ::   ln_rnf_ctl    !: remove runoff dilution on tracers
[12377]118   REAL(wp), PUBLIC                                  ::   rn_sbc_time   !: Time scaling factor for SBC data (seconds in a day)
119   REAL(wp), PUBLIC                                  ::   rn_cbc_time   !: Time scaling factor for CBC data (seconds in a day)
120   LOGICAL , PUBLIC                                  ::   lltrcbc       !: Applying one of the boundary conditions
[3294]121   !
[8665]122   CHARACTER(len=20), PUBLIC, DIMENSION(jp_bdy) :: cn_trc_dflt   ! Default OBC condition for all tracers
123   CHARACTER(len=20), PUBLIC, DIMENSION(jp_bdy) :: cn_trc        ! Choice of boundary condition for tracers
124   INTEGER,           PUBLIC, DIMENSION(jp_bdy) :: nn_trcdmp_bdy !: =T Tracer damping
[10222]125   !
126   ! Vertical axis used in the sediment module
127   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   profsed
[8241]128!$AGRIF_DO_NOT_TREAT
[6140]129   ! External data structure of BDY for TOP. Available elements: cn_obc, ll_trc, trcnow, dmp
[9019]130   TYPE(OBC_DATA), PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET ::   trcdta_bdy   !: bdy external data (local process)
[8241]131!$AGRIF_END_DO_NOT_TREAT
[9019]132   !
[12377]133   !! Substitutions
134#include "do_loop_substitute.h90"
[2715]135   !!----------------------------------------------------------------------
[9598]136   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[5341]137   !! $Id$
[10068]138   !! Software governed by the CeCILL license (see ./LICENSE)
[2715]139   !!----------------------------------------------------------------------
140CONTAINS
141
142   INTEGER FUNCTION trc_alloc()
143      !!-------------------------------------------------------------------
144      !!                    *** ROUTINE trc_alloc ***
145      !!-------------------------------------------------------------------
[10425]146      USE lib_mpp, ONLY: ctl_stop
[2715]147      !!-------------------------------------------------------------------
[7646]148      INTEGER :: ierr(4)
149      !!-------------------------------------------------------------------
150      ierr(:) = 0
[2715]151      !
[12377]152      ALLOCATE( tr(jpi,jpj,jpk,jptra,jpt)                                             ,       & 
[5385]153         &      trc_i(jpi,jpj,jptra)  , trc_o(jpi,jpj,jptra)                          ,       &
[4990]154         &      gtru (jpi,jpj,jptra)  , gtrv (jpi,jpj,jptra)                          ,       &
155         &      gtrui(jpi,jpj,jptra)  , gtrvi(jpi,jpj,jptra)                          ,       &
[7646]156         &      trc_ice_ratio(jptra)  , trc_ice_prescr(jptra) , cn_trc_o(jptra)       ,       &
[5385]157         &      sbc_trc_b(jpi,jpj,jptra), sbc_trc(jpi,jpj,jptra)                      ,       & 
[7646]158         &      cvol(jpi,jpj,jpk)     , trai(jptra)           , qsr_mean(jpi,jpj)     ,       &
159         &      ctrcnm(jptra)         , ctrcln(jptra)         , ctrcun(jptra)         ,       &
160         &      ln_trc_ini(jptra)     ,                                                       &
[6140]161         &      ln_trc_sbc(jptra)     , ln_trc_cbc(jptra)     , ln_trc_obc(jptra)     ,       &
[7646]162         &      STAT = ierr(1)  )
163      !
[9019]164      IF( ln_bdy       )   ALLOCATE( trcdta_bdy(jptra, jp_bdy)  , STAT = ierr(2) )
[7646]165      !
[9019]166      IF (jp_dia3d > 0 )   ALLOCATE( trc3d(jpi,jpj,jpk,jp_dia3d), STAT = ierr(3) )
[7646]167      !
[9019]168      IF (jp_dia2d > 0 )   ALLOCATE( trc2d(jpi,jpj,jpk,jp_dia2d), STAT = ierr(4) )
[7646]169      !
170      trc_alloc = MAXVAL( ierr )
[10425]171      IF( trc_alloc /= 0 )   CALL ctl_stop( 'STOP', 'trc_alloc: failed to allocate arrays' )
[2715]172      !
173   END FUNCTION trc_alloc
174
[186]175   !!======================================================================
176END MODULE trc
Note: See TracBrowser for help on using the repository browser.