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

source: branches/UKMO/AMM15_v3_6_STABLE_package_collate_bgc_diagnostics/NEMOGCM/NEMO/TOP_SRC/trc.F90 @ 10366

Last change on this file since 10366 was 10366, checked in by dford, 5 years ago

Remove visibility, as now available through FABM, and switch from deprecated get_bulk to get_interior.

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