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 2819 for branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC/trc.F90 – NEMO

Ignore:
Timestamp:
2011-08-09T10:29:53+02:00 (13 years ago)
Author:
cetlod
Message:

Improvment of branch dev_r2787_LOCEAN3_TRA_TRP

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r2715 r2819  
    2121   PUBLIC   trc_alloc   ! called by nemogcm.F90 
    2222 
    23    !! passive tracers names and units (read in namelist) 
    24    !! -------------------------------------------------- 
    25    CHARACTER(len=12), PUBLIC, DIMENSION(jptra) ::   ctrcnm     !: tracer name  
    26    CHARACTER(len=12), PUBLIC, DIMENSION(jptra) ::   ctrcun     !: tracer unit 
    27    CHARACTER(len=80), PUBLIC, DIMENSION(jptra) ::   ctrcnl     !: tracer long name  
    28     
    29     
    3023   !! parameters for the control of passive tracers 
    3124   !! -------------------------------------------------- 
    32    INTEGER, PUBLIC                   ::   numnat   !: the number of the passive tracer NAMELIST 
    33    LOGICAL, PUBLIC, DIMENSION(jptra) ::   lutini   !:  initialisation from FILE or not (NAMELIST) 
    34    LOGICAL, PUBLIC, DIMENSION(jptra) ::   lutsav   !:  save the tracer or not 
     25   INTEGER, PUBLIC                                                 ::   numnat        !: the number of the passive tracer NAMELIST 
    3526 
    3627   !! passive tracers fields (before,now,after) 
    3728   !! -------------------------------------------------- 
    38    REAL(wp), PUBLIC ::   trai                          !: initial total tracer 
    39    REAL(wp), PUBLIC ::   areatot                       !: total volume  
    40    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:)   ::   cvol   !: volume correction -degrad option-  
    41    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) ::   trn    !: traceur concentration for now time step 
    42    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) ::   tra    !: traceur concentration for next time step 
    43    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) ::   trb    !: traceur concentration for before time step 
     29   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)               ::  trai           !: initial total tracer 
     30   REAL(wp), PUBLIC                                                ::  areatot        !: total volume  
     31   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  cvol           !: volume correction -degrad option-  
     32   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trn            !: traceur concentration for now time step 
     33   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  tra            !: traceur concentration for next time step 
     34   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trb            !: traceur concentration for before time step 
    4435 
    4536   !! interpolated gradient 
    4637   !!--------------------------------------------------   
    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 
     38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtru           !: hor. gradient at u-points at bottom ocean level 
     39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtrv           !: hor. gradient at v-points at bottom ocean level 
    4940    
    50    !! passive tracers restart (input and output) 
     41   !! passive tracers (input and output) 
    5142   !! ------------------------------------------   
    52    LOGICAL          , PUBLIC ::  ln_rsttr        !: boolean term for restart i/o for passive tracers (namelist) 
    53    LOGICAL          , PUBLIC ::  lrst_trc        !: logical to control the trc restart write 
    54    INTEGER          , PUBLIC ::  nn_dttrc        !: frequency of step on passive tracers 
    55    INTEGER          , PUBLIC ::  nutwrs          !: output FILE for passive tracers restart 
    56    INTEGER          , PUBLIC ::  nutrst          !: logical unit for restart FILE for passive tracers 
    57    INTEGER          , PUBLIC ::  nn_rsttr        !: control of the time step ( 0 or 1 ) for pass. tr. 
    58    CHARACTER(len=50), PUBLIC ::  cn_trcrst_in    !: suffix of pass. tracer restart name (input) 
    59    CHARACTER(len=50), PUBLIC ::  cn_trcrst_out   !: suffix of pass. tracer restart name (output) 
    60     
     43   LOGICAL             , PUBLIC                                    ::  ln_rsttr       !: boolean term for restart i/o for passive tracers (namelist) 
     44   LOGICAL             , PUBLIC                                    ::  lrst_trc       !: logical to control the trc restart write 
     45   INTEGER             , PUBLIC                                    ::  nn_dttrc       !: frequency of step on passive tracers 
     46   INTEGER             , PUBLIC                                    ::  nn_writetrc    !: time step frequency for concentration outputs (namelist) 
     47   INTEGER             , PUBLIC                                    ::  nutwrs         !: output FILE for passive tracers restart 
     48   INTEGER             , PUBLIC                                    ::  nutrst         !: logical unit for restart FILE for passive tracers 
     49   INTEGER             , PUBLIC                                    ::  nn_rsttr       !: control of the time step ( 0 or 1 ) for pass. tr. 
     50   CHARACTER(len = 80) , PUBLIC                                    ::  cn_trcrst_in   !: suffix of pass. tracer restart name (input) 
     51   CHARACTER(len = 80) , PUBLIC                                    ::  cn_trcrst_out  !: suffix of pass. tracer restart name (output) 
     52   REAL(wp)            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::  rdttrc         !: vertical profile of passive tracer time step 
     53   LOGICAL             , PUBLIC                                    ::  ln_trcdta      !: Read inputs data from files 
     54   LOGICAL             , PUBLIC                                    ::  ln_trcdmp      !: internal damping flag 
     55 
    6156   !! information for outputs 
    6257   !! -------------------------------------------------- 
    63    INTEGER , PUBLIC ::   nn_writetrc   !: time step frequency for concentration outputs (namelist) 
    64    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   rdttrc        !: vertical profile of passive tracer time step 
    65     
    66 # if defined key_diatrc && ! defined key_iomput 
     58   TYPE, PUBLIC :: PTRACER                                                            !: Passive tracer type 
     59       CHARACTER(len = 20)  :: clsname  !: short name 
     60       CHARACTER(len = 80)  :: cllname  !: long name 
     61       CHARACTER(len = 20)  :: clunit   !: unit 
     62       LOGICAL              :: llinit   !: read in a file or not 
     63       LOGICAL              :: llsave   !: save the tracer or not 
     64   END TYPE PTRACER 
     65   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcnm         !: tracer name  
     66   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcln         !: trccer field long name 
     67   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ctrcun         !: tracer unit 
     68   LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_ini     !: Initialisation from data input file 
     69   LOGICAL            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_wri     !: save the tracer or not 
     70 
     71   TYPE, PUBLIC :: DIAG                                                               !: passive trcacer ddditional diagnostic type 
     72      CHARACTER(len = 20)  :: sname    !: short name 
     73      CHARACTER(len = 80)  :: lname    !: long name 
     74      CHARACTER(len = 20)  :: units    !: unit 
     75   END TYPE DIAG 
     76 
    6777   !! additional 2D/3D outputs namelist 
    6878   !! -------------------------------------------------- 
    69    INTEGER         , PUBLIC                      ::   nn_writedia   !: frequency of additional arrays outputs(namelist) 
    70    CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia2d) ::   ctrc2d      !: 2d output field name 
    71    CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia2d) ::   ctrc2u      !: 2d output field unit    
    72    CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia3d) ::   ctrc3d      !: 3d output field name 
    73    CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia3d) ::   ctrc3u      !: 3d output field unit 
    74    CHARACTER(len=80), PUBLIC, DIMENSION(jpdia2d) ::   ctrc2l      !: 2d output field long name 
    75    CHARACTER(len=80), PUBLIC, DIMENSION(jpdia3d) ::   ctrc3l      !: 3d output field long name 
     79   REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,  :) ::   trc2d         !: additional 2d outputs array  
     80   REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc3d         !: additional 3d outputs array  
     81   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2d        !: 2d field short name 
     82   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2l        !: 2d field long name 
     83   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc2u        !: 2d field unit 
     84   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3d        !: 3d field short name 
     85   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3l        !: 3d field long name 
     86   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   ctrc3u        !: 3d field unit 
     87   LOGICAL            , PUBLIC                                        ::  ln_diatrc      !: boolean term for additional diagnostic 
     88   INTEGER            , PUBLIC                                        ::  nn_writedia    !: frequency of additional outputs 
    7689 
    77    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,  :) ::   trc2d    !:  additional 2d outputs   
    78    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc3d    !:  additional 3d outputs   
    79 # endif 
    80  
    81 # if defined key_diabio || defined key_trdmld_trc 
    82    !                                                              !!*  namtop_XXX namelist * 
    83    INTEGER , PUBLIC                               ::   nn_writebio   !: time step frequency for biological outputs  
    84    CHARACTER(len=8 ), PUBLIC, DIMENSION(jpdiabio) ::   ctrbio      !: biological trends name       
    85    CHARACTER(len=20), PUBLIC, DIMENSION(jpdiabio) ::   ctrbiu      !: biological trends unit    
    86    CHARACTER(len=80), PUBLIC, DIMENSION(jpdiabio) ::   ctrbil      !: biological trends long name 
    87 # endif 
    88 # if defined key_diabio 
    8990   !! Biological trends 
    9091   !! ----------------- 
    91    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trbio   !: biological trends 
    92 # endif 
    93  
    94     
    95    !! passive tracers data read and at given time_step 
    96    !! -------------------------------------------------- 
    97 # if defined key_dtatrc 
    98    INTEGER , PUBLIC, DIMENSION(jptra) ::   numtr   !: logical unit for passive tracers data 
    99 # endif 
     92   LOGICAL            , PUBLIC                                        ::  ln_diabio      !: boolean term for biological diagnostic 
     93   INTEGER            , PUBLIC                                        ::  nn_writebio    !: frequency of biological outputs 
     94   REAL(wp)           , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  trbio          !: biological trends 
     95   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbio         !: bio field short name 
     96   CHARACTER(len = 80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbil         !: bio field long name 
     97   CHARACTER(len = 20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::  ctrbiu         !: bio field unit 
    10098 
    10199   !!---------------------------------------------------------------------- 
     
    113111      !!------------------------------------------------------------------- 
    114112      ! 
    115       ALLOCATE( cvol(jpi,jpj,jpk      ) ,                           & 
    116          &      trn (jpi,jpj,jpk,jptra) ,                           & 
    117          &      tra (jpi,jpj,jpk,jptra) ,                           & 
    118          &      trb (jpi,jpj,jpk,jptra) ,                           & 
    119          &      gtru(jpi,jpj    ,jptra) , gtrv(jpi,jpj,jptra) ,     & 
    120 # if defined key_diatrc && ! defined key_iomput 
    121          &      trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d), & 
    122 # endif 
    123 # if defined key_diabio 
    124          &      trbio(jpi,jpj,jpk,jpdiabio),                        & 
    125 #endif 
    126                rdttrc(jpk) ,  STAT=trc_alloc )       
     113      ALLOCATE( trn(jpi,jpj,jpk,jptra), trb(jpi,jpj,jpk,jptra), tra(jpi,jpj,jpk,jptra),       &   
     114         &      gtru(jpi,jpj,jpk)     , gtrv(jpi,jpj,jpk)                             ,       & 
     115         &      cvol(jpi,jpj,jpk)     , rdttrc(jpk)           , trai(jptra)           ,       & 
     116         &      ctrcnm(jptra)         , ctrcln(jptra)         , ctrcun(jptra)         ,       &  
     117         &      ln_trc_ini(jptra)     , ln_trc_wri(jptra)                             ,  STAT = trc_alloc  )   
    127118 
    128119      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays') 
Note: See TracChangeset for help on using the changeset viewer.