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/branches/2019/dev_r11219_TOP-01_cethe_PISCES_LBC/src/TOP – NEMO

source: NEMO/branches/2019/dev_r11219_TOP-01_cethe_PISCES_LBC/src/TOP/trc.F90 @ 11609

Last change on this file since 11609 was 11609, checked in by cetlod, 5 years ago

dev_PISCES_LBC : minor improvments

  • 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 ::   numnat_ref = -1   !: reference passive tracer namelist_top_ref
21   INTEGER, PUBLIC ::   numnat_cfg = -1   !: reference passive tracer namelist_top_cfg
22   INTEGER, PUBLIC ::   numont     = -1   !: reference passive tracer namelist output output.namelist.top
23   INTEGER, PUBLIC ::   numtrc_ref = -1   !: reference passive tracer namelist_top_ref
24   INTEGER, PUBLIC ::   numtrc_cfg = -1   !: reference passive tracer namelist_top_cfg
25   INTEGER, PUBLIC ::   numonr     = -1   !: reference passive tracer namelist output output.namelist.top
26   INTEGER, PUBLIC ::   numstr            !: tracer statistics
27   INTEGER, PUBLIC ::   numrtr            !: trc restart (read )
28   INTEGER, PUBLIC ::   numrtw            !: trc restart ( write )
[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-
35   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  trn            !: tracer concentration for now time step
36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  tra            !: tracer concentration for next time step
37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  trb            !: tracer concentration for before time step
38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  sbc_trc_b      !: Before sbc fluxes for tracers
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  sbc_trc        !: Now sbc fluxes for tracers
[186]40
[9019]41   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  trc_i          !: prescribed tracer concentration in sea ice for SBC
42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  ) ::  trc_o          !: prescribed tracer concentration in ocean for SBC
43   INTEGER             , PUBLIC                            ::  nn_ice_tr      !: handling of sea ice tracers
[5385]44
[2528]45   !! interpolated gradient
46   !!-------------------------------------------------- 
[9019]47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  gtru           !: hor. gradient at u-points at bottom ocean level
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  gtrv           !: hor. gradient at v-points at bottom ocean level
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  gtrui          !: hor. gradient at u-points at top    ocean level
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  gtrvi          !: hor. gradient at v-points at top    ocean level
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  qsr_mean        !: daily mean qsr
[186]52   
[3294]53   !! passive tracers  (input and output)
[945]54   !! ------------------------------------------ 
[9019]55   LOGICAL             , PUBLIC ::   ln_rsttr           !: boolean term for restart i/o for passive tracers (namelist)
56   LOGICAL             , PUBLIC ::   lrst_trc           !: logical to control the trc restart write
57   INTEGER             , PUBLIC ::   nn_writetrc        !: time step frequency for concentration outputs (namelist)
58   INTEGER             , PUBLIC ::   nutwrs             !: output FILE for passive tracers restart
59   INTEGER             , PUBLIC ::   nutrst             !: logical unit for restart FILE for passive tracers
60   INTEGER             , PUBLIC ::   nn_rsttr           !: control of the time step ( 0 or 1 ) for pass. tr.
61   CHARACTER(len = 80) , PUBLIC ::   cn_trcrst_in       !: suffix of pass. tracer restart name (input)
62   CHARACTER(len = 256), PUBLIC ::   cn_trcrst_indir    !: restart input directory
63   CHARACTER(len = 80) , PUBLIC ::   cn_trcrst_out      !: suffix of pass. tracer restart name (output)
64   CHARACTER(len = 256), PUBLIC ::   cn_trcrst_outdir   !: restart output directory
65   REAL(wp)            , PUBLIC ::   rdttrc             !: passive tracer time step
66   REAL(wp)            , PUBLIC ::   r2dttrc            !: = 2*rdttrc except at nit000 (=rdttrc) if neuler=0
67   LOGICAL             , PUBLIC ::   ln_top_euler       !: boolean term for euler integration
68   LOGICAL             , PUBLIC ::   ln_trcdta          !: Read inputs data from files
[11609]69   LOGICAL             , PUBLIC ::   ln_trcbc           !: Enable surface, lateral or open boundaries conditions
[9019]70   LOGICAL             , PUBLIC ::   ln_trcdmp          !: internal damping flag
71   LOGICAL             , PUBLIC ::   ln_trcdmp_clo      !: internal damping flag on closed seas
72   INTEGER             , PUBLIC ::   nittrc000          !: first time step of passive tracers model
73   LOGICAL             , PUBLIC ::   l_trcdm2dc         !: Diurnal cycle for TOP
[3294]74
[5385]75   !! Information for the ice module for tracers
76   !! ------------------------------------------
[9019]77   TYPE, PUBLIC ::   TRC_I_NML         !: Ice tracer namelist structure
78         REAL(wp)         :: trc_ratio    ! ice-ocean trc ratio
79         REAL(wp)         :: trc_prescr   ! prescribed ice trc cc
80         CHARACTER(len=2) :: ctrc_o       ! choice of ocean trc cc
[5385]81   END TYPE
[9019]82   !
83   REAL(wp)        , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   trc_ice_ratio    !: ice-ocean tracer ratio
84   REAL(wp)        , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   trc_ice_prescr   !: prescribed ice trc cc
85   CHARACTER(len=2), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   cn_trc_o         !: choice of ocean tracer cc
[5385]86
87
[186]88   !! information for outputs
89   !! --------------------------------------------------
[9019]90   TYPE, PUBLIC ::   PTRACER        !: Passive tracer type
91      CHARACTER(len=20) ::   clsname   ! short name
92      CHARACTER(len=80) ::   cllname   ! long name
93      CHARACTER(len=20) ::   clunit    ! unit
94      LOGICAL           ::   llinit    ! read in a file or not
95      LOGICAL           ::   llsbc     ! read in a file or not
96      LOGICAL           ::   llcbc     ! read in a file or not
97      LOGICAL           ::   llobc     ! read in a file or not
[3294]98   END TYPE PTRACER
[9019]99   !
100   CHARACTER(len=20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ctrcnm   !: tracer name
101   CHARACTER(len=80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ctrcln   !: trccer field long name
102   CHARACTER(len=20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ctrcun   !: tracer unit
103   !
104   TYPE, PUBLIC ::   DIAG         !: Passive trcacer ddditional diagnostic type
105      CHARACTER(len=20) ::   sname   ! short name
106      CHARACTER(len=80) ::   lname   ! long name
107      CHARACTER(len=20) ::   units   ! unit
[3294]108   END TYPE DIAG
[9019]109   !
110   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc3d   !: 3D diagnostics for tracers
111   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc2d   !: 2D diagnostics for tracers
[3294]112
[3680]113   !! information for inputs
114   !! --------------------------------------------------
[9019]115   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ln_trc_ini    !: Initialisation from data input file
116   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ln_trc_obc    !: Use open boundary condition data
117   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ln_trc_sbc    !: Use surface boundary condition data
118   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ln_trc_cbc    !: Use coastal boundary condition data
119   LOGICAL , PUBLIC                                  ::   ln_rnf_ctl    !: remove runoff dilution on tracers
[11222]120   REAL(wp), PUBLIC                                  ::   rn_sbc_time   !: Time scaling factor for SBC data (seconds in a day)
121   REAL(wp), PUBLIC                                  ::   rn_cbc_time   !: Time scaling factor for CBC data (seconds in a day)
122   LOGICAL , PUBLIC                                  ::   lltrcbc       !: Applying one of the boundary conditions
[3294]123   !
[8665]124   CHARACTER(len=20), PUBLIC, DIMENSION(jp_bdy) :: cn_trc_dflt   ! Default OBC condition for all tracers
125   CHARACTER(len=20), PUBLIC, DIMENSION(jp_bdy) :: cn_trc        ! Choice of boundary condition for tracers
126   INTEGER,           PUBLIC, DIMENSION(jp_bdy) :: nn_trcdmp_bdy !: =T Tracer damping
[10222]127   !
128   ! Vertical axis used in the sediment module
129   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   profsed
[8241]130!$AGRIF_DO_NOT_TREAT
[6140]131   ! External data structure of BDY for TOP. Available elements: cn_obc, ll_trc, trcnow, dmp
[9019]132   TYPE(OBC_DATA), PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET ::   trcdta_bdy   !: bdy external data (local process)
[8241]133!$AGRIF_END_DO_NOT_TREAT
[9019]134   !
[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      !
[3294]152      ALLOCATE( trn(jpi,jpj,jpk,jptra), trb(jpi,jpj,jpk,jptra), tra(jpi,jpj,jpk,jptra),       & 
[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.