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.
Changeset 7646 for trunk/NEMOGCM/NEMO/TOP_SRC/trc.F90 – NEMO

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

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.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r6140 r7646  
    1414   USE par_oce 
    1515   USE par_trc 
    16 #if defined key_bdy 
    17    USE bdy_oce, only: nb_bdy, OBC_DATA 
    18 #endif 
     16   USE bdy_oce, only: ln_bdy, nb_bdy, OBC_DATA 
    1917    
    2018   IMPLICIT NONE 
     
    2826   INTEGER, PUBLIC                                                 ::   numnat_cfg = -1   !: logical unit for the reference passive tracer namelist_top_cfg 
    2927   INTEGER, PUBLIC                                                 ::   numont     = -1   !: logical unit for the reference passive tracer namelist output output.namelist.top 
     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 
    3031   INTEGER, PUBLIC                                                 ::   numstr        !: logical unit for tracer statistics 
    3132   INTEGER, PUBLIC                                                 ::   numrtr        !: logical unit for trc restart (read ) 
     
    6869   CHARACTER(len = 256), PUBLIC                                    ::  cn_trcrst_outdir  !: restart output directory 
    6970   REAL(wp)            , PUBLIC                                    ::  rdttrc         !: passive tracer time step 
    70    LOGICAL             , PUBLIC                                    ::  ln_top_euler  !: boolean term for euler integration  
     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  
    7173   LOGICAL             , PUBLIC                                    ::  ln_trcdta      !: Read inputs data from files 
    7274   LOGICAL             , PUBLIC                                    ::  ln_trcdmp      !: internal damping flag 
    7375   LOGICAL             , PUBLIC                                    ::  ln_trcdmp_clo  !: internal damping flag on closed seas 
    74    INTEGER             , PUBLIC                                    ::  nittrc000       !: first time step of passive tracers model 
     76   INTEGER             , PUBLIC                                    ::  nittrc000      !: first time step of passive tracers model 
    7577   LOGICAL             , PUBLIC                                    ::  l_trcdm2dc     !: Diurnal cycle for TOP 
    7678 
     
    8385   END TYPE 
    8486 
    85    REAL(wp), DIMENSION(jptra), PUBLIC         :: trc_ice_ratio, & ! ice-ocean tracer ratio 
    86                                                  trc_ice_prescr   ! prescribed ice trc cc 
    87    CHARACTER(len=2), DIMENSION(jptra), PUBLIC :: cn_trc_o ! choice of ocean tracer cc 
     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 
     90 
    8891 
    8992   !! information for outputs 
     
    9497       CHARACTER(len = 20)  :: clunit   !: unit 
    9598       LOGICAL              :: llinit   !: read in a file or not 
    96 #if defined  key_my_trc 
    9799       LOGICAL              :: llsbc   !: read in a file or not 
    98100       LOGICAL              :: llcbc   !: read in a file or not 
    99101       LOGICAL              :: llobc   !: read in a file or not 
    100 #endif 
    101        LOGICAL              :: llsave   !: save the tracer or not 
    102102   END TYPE PTRACER 
     103 
    103104   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcnm         !: tracer name  
    104105   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcln         !: trccer field long name 
    105106   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcun         !: tracer unit 
    106    LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_wri     !: save the tracer or not 
    107107 
    108108   TYPE, PUBLIC :: DIAG                                                               !: passive trcacer ddditional diagnostic type 
     
    112112   END TYPE DIAG 
    113113 
     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 
    114117   !! information for inputs 
    115118   !! -------------------------------------------------- 
    116    LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_ini     !: Initialisation from data input file 
    117    LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_obc     !: Use open boundary condition data 
    118    LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_sbc     !: Use surface boundary condition data 
    119    LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_cbc     !: Use coastal boundary condition data 
    120  
    121    !! additional 2D/3D outputs namelist 
    122    !! -------------------------------------------------- 
    123    REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,  :) ::   trc2d         !: additional 2d outputs array  
    124    REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc3d         !: additional 3d outputs array  
    125    CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2d        !: 2d field short name 
    126    CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2l        !: 2d field long name 
    127    CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2u        !: 2d field unit 
    128    CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3d        !: 3d field short name 
    129    CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3l        !: 3d field long name 
    130    CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3u        !: 3d field unit 
    131    LOGICAL            , PUBLIC                                        ::  ln_diatrc      !: boolean term for additional diagnostic 
    132    INTEGER            , PUBLIC                                        ::  nn_writedia    !: frequency of additional outputs 
    133  
    134    !! Biological trends 
    135    !! ----------------- 
    136    LOGICAL            , PUBLIC                                        ::  ln_diabio      !: boolean term for biological diagnostic 
    137    INTEGER            , PUBLIC                                        ::  nn_writebio    !: frequency of biological outputs 
    138    REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  trbio          !: biological trends 
    139    CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbio         !: bio field short name 
    140    CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbil         !: bio field long name 
    141    CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbiu         !: bio field unit 
     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) 
     125 
    142126 
    143127   !! variables to average over physics over passive tracer sub-steps. 
     
    189173# endif 
    190174   ! 
    191 #if defined key_bdy 
    192175   CHARACTER(len=20), PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  cn_trc_dflt          ! Default OBC condition for all tracers 
    193176   CHARACTER(len=20), PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  cn_trc               ! Choice of boundary condition for tracers 
     
    195178   ! External data structure of BDY for TOP. Available elements: cn_obc, ll_trc, trcnow, dmp 
    196179   TYPE(OBC_DATA),    PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET ::  trcdta_bdy           !: bdy external data (local process) 
    197 #endif 
    198180   ! 
    199181 
     
    211193      USE lib_mpp, ONLY: ctl_warn 
    212194      !!------------------------------------------------------------------- 
     195      INTEGER :: ierr(4) 
     196      !!------------------------------------------------------------------- 
     197      ierr(:) = 0 
    213198      ! 
    214199      ALLOCATE( trn(jpi,jpj,jpk,jptra), trb(jpi,jpj,jpk,jptra), tra(jpi,jpj,jpk,jptra),       &   
     
    216201         &      gtru (jpi,jpj,jptra)  , gtrv (jpi,jpj,jptra)                          ,       & 
    217202         &      gtrui(jpi,jpj,jptra)  , gtrvi(jpi,jpj,jptra)                          ,       & 
     203         &      trc_ice_ratio(jptra)  , trc_ice_prescr(jptra) , cn_trc_o(jptra)       ,       & 
    218204         &      sbc_trc_b(jpi,jpj,jptra), sbc_trc(jpi,jpj,jptra)                      ,       &   
    219          &      cvol(jpi,jpj,jpk)     , trai(jptra)                                   ,       & 
    220          &      ctrcnm(jptra)         , ctrcln(jptra)         , ctrcun(jptra)         ,       &  
    221          &      ln_trc_ini(jptra)     , ln_trc_wri(jptra)     , qsr_mean(jpi,jpj)     ,       & 
    222 #if defined key_my_trc 
     205         &      cvol(jpi,jpj,jpk)     , trai(jptra)           , qsr_mean(jpi,jpj)     ,       & 
     206         &      ctrcnm(jptra)         , ctrcln(jptra)         , ctrcun(jptra)         ,       & 
     207         &      ln_trc_ini(jptra)     ,                                                       & 
    223208         &      ln_trc_sbc(jptra)     , ln_trc_cbc(jptra)     , ln_trc_obc(jptra)     ,       & 
    224 #endif 
    225 #if defined key_bdy 
    226          &      cn_trc_dflt(nb_bdy)   , cn_trc(nb_bdy)        , nn_trcdmp_bdy(nb_bdy) ,       & 
     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) ,       & 
    227213         &      trcdta_bdy(jptra,nb_bdy)                                              ,       & 
    228 #endif 
    229          &      STAT = trc_alloc  ) 
    230  
     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 ) 
    231222      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays') 
    232223      ! 
Note: See TracChangeset for help on using the changeset viewer.