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 trunk/NEMOGCM/NEMO/TOP_SRC – NEMO

source: trunk/NEMOGCM/NEMO/TOP_SRC/trc.F90 @ 7873

Last change on this file since 7873 was 7646, checked in by timgraham, 7 years ago

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

  • Property svn:keywords set to Id
File size: 16.7 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   !!----------------------------------------------------------------------
[945]10#if defined key_top
[186]11   !!----------------------------------------------------------------------
[945]12   !!   'key_top'                                                TOP models
13   !!----------------------------------------------------------------------
[186]14   USE par_oce
15   USE par_trc
[7646]16   USE bdy_oce, only: ln_bdy, nb_bdy, OBC_DATA
[945]17   
[186]18   IMPLICIT NONE
19   PUBLIC
20
[2715]21   PUBLIC   trc_alloc   ! called by nemogcm.F90
22
[186]23   !! parameters for the control of passive tracers
[4147]24   !! ---------------------------------------------   
25   INTEGER, PUBLIC                                                 ::   numnat_ref = -1   !: logical unit for the reference passive tracer namelist_top_ref
26   INTEGER, PUBLIC                                                 ::   numnat_cfg = -1   !: logical unit for the reference passive tracer namelist_top_cfg
27   INTEGER, PUBLIC                                                 ::   numont     = -1   !: logical unit for the reference passive tracer namelist output output.namelist.top
[7646]28   INTEGER, PUBLIC                                                 ::   numtrc_ref = -1   !: logical unit for the reference passive tracer namelist_top_ref
29   INTEGER, PUBLIC                                                 ::   numtrc_cfg = -1   !: logical unit for the reference passive tracer namelist_top_cfg
30   INTEGER, PUBLIC                                                 ::   numonr     = -1   !: logical unit for the reference passive tracer namelist output output.namelist.top
[3294]31   INTEGER, PUBLIC                                                 ::   numstr        !: logical unit for tracer statistics
[3680]32   INTEGER, PUBLIC                                                 ::   numrtr        !: logical unit for trc restart (read )
33   INTEGER, PUBLIC                                                 ::   numrtw        !: logical unit for trc restart ( write )
[186]34
35   !! passive tracers fields (before,now,after)
36   !! --------------------------------------------------
[3294]37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)               ::  trai           !: initial total tracer
38   REAL(wp), PUBLIC                                                ::  areatot        !: total volume
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  cvol           !: volume correction -degrad option-
[5385]40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trn            !: tracer concentration for now time step
41   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  tra            !: tracer concentration for next time step
42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trb            !: tracer concentration for before time step
43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  sbc_trc_b      !: Before sbc fluxes for tracers
44   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  sbc_trc        !: Now sbc fluxes for tracers
[186]45
[5385]46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  trc_i          !: prescribed tracer concentration in sea ice for SBC
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  trc_o          !: prescribed tracer concentration in ocean for SBC
48   INTEGER             , PUBLIC                                    ::  nn_ice_tr      !: handling of sea ice tracers
49
[2528]50   !! interpolated gradient
51   !!-------------------------------------------------- 
[3294]52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtru           !: hor. gradient at u-points at bottom ocean level
53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtrv           !: hor. gradient at v-points at bottom ocean level
[4990]54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtrui          !: hor. gradient at u-points at top    ocean level
55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtrvi          !: hor. gradient at v-points at top    ocean level
[5385]56   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)             ::  qsr_mean        !: daily mean qsr
[186]57   
[3294]58   !! passive tracers  (input and output)
[945]59   !! ------------------------------------------ 
[3294]60   LOGICAL             , PUBLIC                                    ::  ln_rsttr       !: boolean term for restart i/o for passive tracers (namelist)
61   LOGICAL             , PUBLIC                                    ::  lrst_trc       !: logical to control the trc restart write
62   INTEGER             , PUBLIC                                    ::  nn_writetrc    !: time step frequency for concentration outputs (namelist)
63   INTEGER             , PUBLIC                                    ::  nutwrs         !: output FILE for passive tracers restart
64   INTEGER             , PUBLIC                                    ::  nutrst         !: logical unit for restart FILE for passive tracers
65   INTEGER             , PUBLIC                                    ::  nn_rsttr       !: control of the time step ( 0 or 1 ) for pass. tr.
66   CHARACTER(len = 80) , PUBLIC                                    ::  cn_trcrst_in   !: suffix of pass. tracer restart name (input)
[5341]67   CHARACTER(len = 256), PUBLIC                                    ::  cn_trcrst_indir  !: restart input directory
[3294]68   CHARACTER(len = 80) , PUBLIC                                    ::  cn_trcrst_out  !: suffix of pass. tracer restart name (output)
[5341]69   CHARACTER(len = 256), PUBLIC                                    ::  cn_trcrst_outdir  !: restart output directory
[6140]70   REAL(wp)            , PUBLIC                                    ::  rdttrc         !: passive tracer time step
[7646]71   REAL(wp)            , PUBLIC                                    ::  r2dttrc        !: = 2*rdttrc except at nit000 (=rdttrc) if neuler=0
72   LOGICAL             , PUBLIC                                    ::  ln_top_euler   !: boolean term for euler integration
[3294]73   LOGICAL             , PUBLIC                                    ::  ln_trcdta      !: Read inputs data from files
74   LOGICAL             , PUBLIC                                    ::  ln_trcdmp      !: internal damping flag
[4148]75   LOGICAL             , PUBLIC                                    ::  ln_trcdmp_clo  !: internal damping flag on closed seas
[7646]76   INTEGER             , PUBLIC                                    ::  nittrc000      !: first time step of passive tracers model
[5385]77   LOGICAL             , PUBLIC                                    ::  l_trcdm2dc     !: Diurnal cycle for TOP
[3294]78
[5385]79   !! Information for the ice module for tracers
80   !! ------------------------------------------
81   TYPE TRC_I_NML                    !--- Ice tracer namelist structure
82         REAL(wp)         :: trc_ratio  ! ice-ocean trc ratio
83         REAL(wp)         :: trc_prescr ! prescribed ice trc cc
84         CHARACTER(len=2) :: ctrc_o     ! choice of ocean trc cc
85   END TYPE
86
[7646]87   REAL(wp)        , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)  :: trc_ice_ratio      ! ice-ocean tracer ratio
88   REAL(wp)        , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)  :: trc_ice_prescr     ! prescribed ice trc cc
89   CHARACTER(len=2), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)  :: cn_trc_o ! choice of ocean tracer cc
[5385]90
[7646]91
[186]92   !! information for outputs
93   !! --------------------------------------------------
[3294]94   TYPE, PUBLIC :: PTRACER                                                            !: Passive tracer type
95       CHARACTER(len = 20)  :: clsname  !: short name
96       CHARACTER(len = 80)  :: cllname  !: long name
97       CHARACTER(len = 20)  :: clunit   !: unit
98       LOGICAL              :: llinit   !: read in a file or not
[6140]99       LOGICAL              :: llsbc   !: read in a file or not
100       LOGICAL              :: llcbc   !: read in a file or not
101       LOGICAL              :: llobc   !: read in a file or not
[3294]102   END TYPE PTRACER
[7646]103
[3294]104   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcnm         !: tracer name
105   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcln         !: trccer field long name
106   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcun         !: tracer unit
107
108   TYPE, PUBLIC :: DIAG                                                               !: passive trcacer ddditional diagnostic type
109      CHARACTER(len = 20)  :: sname    !: short name
110      CHARACTER(len = 80)  :: lname    !: long name
111      CHARACTER(len = 20)  :: units    !: unit
112   END TYPE DIAG
113
[7646]114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trc3d          !: 3D diagnostics for tracers
115   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trc2d          !: 2D diagnostics for tracers
116
[3680]117   !! information for inputs
118   !! --------------------------------------------------
[7646]119   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_ini     !: Initialisation from data input file
120   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_obc     !: Use open boundary condition data
121   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_sbc     !: Use surface boundary condition data
122   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_cbc     !: Use coastal boundary condition data
123   LOGICAL , PUBLIC                                     ::  ln_rnf_ctl     !: remove runoff dilution on tracers
124   REAL(wp), PUBLIC                                     ::  rn_bc_time     !: Time scaling factor for SBC and CBC data (seconds in a day)
[3680]125
[945]126
[3294]127   !! variables to average over physics over passive tracer sub-steps.
128   !! ----------------------------------------------------------------
129   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  un_tm       !: i-horizontal velocity average     [m/s]
130   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  vn_tm       !: j-horizontal velocity average     [m/s]
131   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  tsn_tm      !: t/s average     [m/s]
132   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  avt_tm      !: vertical diffusivity coeff. at  w-point   [m2/s]
133   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  rhop_tm     !:
134# if defined key_zdfddm
135   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  avs_tm      !: vertical double diffusivity coeff. at w-point   [m/s]
[1077]136# endif
[3294]137#if defined key_trabbl
138   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  ahu_bbl_tm  !: u-, w-points
139   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  ahv_bbl_tm  !: j-direction slope at u-, w-points
140   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  utr_bbl_tm  !: j-direction slope at u-, w-points
141   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  vtr_bbl_tm  !: j-direction slope at u-, w-points
142#endif
143   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  sshn_tm     !: average ssh for the now step [m]
144   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  sshb_hold   !:hold sshb from the beginning of each sub-stepping[m] 
[1077]145
[3294]146   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  rnf_tm     !: river runoff
147   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  h_rnf_tm   !: depth in metres to the bottom of the relevant grid box
148   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  hmld_tm    !: mixed layer depth average [m]
149   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  fr_i_tm    !: average ice fraction     [m/s]
150   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  emp_tm     !: freshwater budget: volume flux [Kg/m2/s]
[4148]151   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  fmmflx_tm  !: freshwater budget: freezing/melting [Kg/m2/s]
[3294]152   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  emp_b_hold !: hold emp from the beginning of each sub-stepping[m] 
153   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  qsr_tm     !: solar radiation average [m]
154   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  wndm_tm    !: 10m wind average [m]
155   !
156
157   ! Temporary physical arrays for sub_stepping
158   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  tsn_temp
159   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  un_temp,vn_temp,wn_temp     !: hold current values of avt, un, vn, wn
160   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  avt_temp, rhop_temp     !: hold current values of avt, un, vn, wn
161   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  sshn_temp, sshb_temp, ssha_temp, rnf_temp,h_rnf_temp
162   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  hdivn_temp, rotn_temp
163   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  hdivb_temp, rotb_temp
164   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  hmld_temp, qsr_temp, fr_i_temp,wndm_temp
[4148]165   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  emp_temp, fmmflx_temp, emp_b_temp
[3294]166   !
167#if defined key_trabbl
168   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  ahu_bbl_temp, ahv_bbl_temp, utr_bbl_temp, vtr_bbl_temp !: hold current values
169#endif
170   !
171# if defined key_zdfddm
172   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  avs_temp      !: salinity vertical diffusivity coeff. at w-point   [m/s]
[945]173# endif
[3294]174   !
[6140]175   CHARACTER(len=20), PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  cn_trc_dflt          ! Default OBC condition for all tracers
176   CHARACTER(len=20), PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  cn_trc               ! Choice of boundary condition for tracers
177   INTEGER,           PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  nn_trcdmp_bdy        !: =T Tracer damping
178   ! External data structure of BDY for TOP. Available elements: cn_obc, ll_trc, trcnow, dmp
179   TYPE(OBC_DATA),    PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET ::  trcdta_bdy           !: bdy external data (local process)
180   !
[186]181
[2715]182   !!----------------------------------------------------------------------
183   !! NEMO/TOP 3.3.1 , NEMO Consortium (2010)
[5341]184   !! $Id$
[2715]185   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
186   !!----------------------------------------------------------------------
187CONTAINS
188
189   INTEGER FUNCTION trc_alloc()
190      !!-------------------------------------------------------------------
191      !!                    *** ROUTINE trc_alloc ***
192      !!-------------------------------------------------------------------
193      USE lib_mpp, ONLY: ctl_warn
194      !!-------------------------------------------------------------------
[7646]195      INTEGER :: ierr(4)
196      !!-------------------------------------------------------------------
197      ierr(:) = 0
[2715]198      !
[3294]199      ALLOCATE( trn(jpi,jpj,jpk,jptra), trb(jpi,jpj,jpk,jptra), tra(jpi,jpj,jpk,jptra),       & 
[5385]200         &      trc_i(jpi,jpj,jptra)  , trc_o(jpi,jpj,jptra)                          ,       &
[4990]201         &      gtru (jpi,jpj,jptra)  , gtrv (jpi,jpj,jptra)                          ,       &
202         &      gtrui(jpi,jpj,jptra)  , gtrvi(jpi,jpj,jptra)                          ,       &
[7646]203         &      trc_ice_ratio(jptra)  , trc_ice_prescr(jptra) , cn_trc_o(jptra)       ,       &
[5385]204         &      sbc_trc_b(jpi,jpj,jptra), sbc_trc(jpi,jpj,jptra)                      ,       & 
[7646]205         &      cvol(jpi,jpj,jpk)     , trai(jptra)           , qsr_mean(jpi,jpj)     ,       &
206         &      ctrcnm(jptra)         , ctrcln(jptra)         , ctrcun(jptra)         ,       &
207         &      ln_trc_ini(jptra)     ,                                                       &
[6140]208         &      ln_trc_sbc(jptra)     , ln_trc_cbc(jptra)     , ln_trc_obc(jptra)     ,       &
[7646]209         &      STAT = ierr(1)  )
210      !
211      IF ( ln_bdy ) THEN
212         ALLOCATE( cn_trc_dflt(nb_bdy)   , cn_trc(nb_bdy)     , nn_trcdmp_bdy(nb_bdy) ,       &
[6140]213         &      trcdta_bdy(jptra,nb_bdy)                                              ,       &
[7646]214         &      STAT = ierr(2)  )
215      ENDIF
216      !
217      IF (jp_dia3d > 0 ) ALLOCATE( trc3d(jpi,jpj,jpk,jp_dia3d), STAT = ierr(3) )
218      !
219      IF (jp_dia2d > 0 ) ALLOCATE( trc2d(jpi,jpj,jpk,jp_dia2d), STAT = ierr(4) )
220      !
221      trc_alloc = MAXVAL( ierr )
[2715]222      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays')
223      !
224   END FUNCTION trc_alloc
225
[945]226#else
227   !!----------------------------------------------------------------------
228   !!  Empty module :                                     No passive tracer
229   !!----------------------------------------------------------------------
[439]230#endif
231
[186]232   !!======================================================================
233END MODULE trc
Note: See TracBrowser for help on using the repository browser.