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 7198 – NEMO

Changeset 7198


Ignore:
Timestamp:
2016-11-04T18:58:24+01:00 (7 years ago)
Author:
lovato
Message:

New top interface : merge with dev_r7012_ROBUST5_CMCC (#1783) and update sette.sh

Location:
branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/GYRE_PISCES/EXP00/namelist_top_cfg

    r7068 r7198  
    99&namtrc     !   tracers definition 
    1010!----------------------------------------------------------------------- 
    11    jptra        =  6 
     11   jp_bgc        =  6 
    1212! 
    1313   ln_pisces     =  .true. 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/ORCA2_LIM3_TRC/EXP00/namelist_top_cfg

    r7124 r7198  
    1616&namtrc          !   tracers definition 
    1717!----------------------------------------------------------------------- 
    18    jptra         =  0           !  Number of passive tracers of the BGC model 
     18   jp_bgc        =  0           !  Number of passive tracers of the BGC model 
    1919! 
    2020   ln_pisces     =  .false.     !  Run PISCES BGC model 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/ORCA2_LIM_PISCES/EXP00/namelist_top_cfg

    r7068 r7198  
    1010&namtrc     !   tracers definition 
    1111!----------------------------------------------------------------------- 
    12    jptra        =  24 
     12   jp_bgc        =  24 
    1313! 
    1414   ln_pisces     =  .true. 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/ORCA2_OFF_PISCES/EXP00/namelist_top_cfg

    r7174 r7198  
    1010&namtrc     !   tracers definition 
    1111!----------------------------------------------------------------------- 
    12    jptra        =  24 
     12   jp_bgc        =  24 
    1313! 
    1414   ln_pisces     =  .true. 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/CONFIG/SHARED/namelist_top_ref

    r7103 r7198  
    2626&namtrc          !   tracers definition 
    2727!----------------------------------------------------------------------- 
    28    jptra         =  0           !  Number of passive tracers of the BGC model 
     28   jp_bgc        =  0           !  Number of passive tracers of the BGC model 
    2929! 
    3030   ln_pisces     =  .false.     !  Run PISCES BGC model  
     
    3838   ln_trcdmp     =  .false.  !  add a damping termn (T) or not (F) 
    3939   ln_trcdmp_clo =  .false.  !  damping term (T) or not (F) on closed seas 
     40! 
     41   jp_dia3d      = 0         ! Number of 3D diagnostic variables 
     42   jp_dia2d      = 0         ! Number of 2D diagnostic variables 
    4043!                !           !                                         !            !                               ! 
    4144!                !    name   !           title of the field            !   units    ! initial data from file or not !  
     
    136139   cn_dir_cbc    =  './'     !  root directory for the location of COASTAL data files 
    137140   cn_dir_obc    =  './'     !  root directory for the location of OPEN data files 
     141   ln_rnf_ctl    = .false.   !  Remove runoff dilution on tracers with absent river load 
     142   rn_bc_time    =  86400.   !  Time scaling factor for SBC and CBC data (seconds in a day) 
    138143/ 
    139144!---------------------------------------------------------------------- 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcsms_my_trc.F90

    r7097 r7198  
    1515   USE trd_oce 
    1616   USE trdtrc 
    17    USE trcbc, only : trc_bc_read 
     17   USE trcbc, only : trc_bc 
    1818 
    1919   IMPLICIT NONE 
     
    5454      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrmyt ) 
    5555 
    56       CALL trc_bc_read ( kt )       ! tracers: surface and lateral Boundary Conditions 
     56      CALL trc_bc ( kt )       ! tracers: surface and lateral Boundary Conditions 
    5757 
    5858      ! add here the call to BGC model 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/oce_trc.F90

    r7162 r7198  
    6464   USE sbc_oce , ONLY :   fmmflx     =>    fmmflx     !: freshwater budget: volume flux               [Kg/m2/s] 
    6565   USE sbc_oce , ONLY :   rnf        =>    rnf        !: river runoff   [Kg/m2/s] 
     66   USE sbc_oce , ONLY :   rnf_b      =>    rnf_b      !: river runoff at previus step   [Kg/m2/s] 
    6667   USE sbc_oce , ONLY :   ln_dm2dc   =>    ln_dm2dc   !: Diurnal Cycle  
    6768   USE sbc_oce , ONLY :   ln_cpl     =>    ln_cpl     !: ocean-atmosphere coupled formulation 
     
    7879   USE sbcrnf  , ONLY :   h_rnf      =>    h_rnf      !: river runoff   [Kg/m2/s] 
    7980   USE sbcrnf  , ONLY :   nk_rnf     =>    nk_rnf     !: depth of runoff in model level 
     81   USE sbcrnf  , ONLY :   rn_rfact   =>    rn_rfact   !: multiplicative factor for runoff 
    8082 
    8183   USE trc_oce 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/par_trc.F90

    r7068 r7198  
    2121   INTEGER, PUBLIC,  PARAMETER :: jpmaxtrc = 100  ! Maximum number of tracers 
    2222 
    23    INTEGER, PUBLIC             :: jptra           ! Total number of tracers 
     23   INTEGER, PUBLIC             :: jptra           !: Total number of passive tracers 
    2424   INTEGER, PUBLIC             :: jp_pisces       !: number of passive tracers in PISCES model 
    2525   INTEGER, PUBLIC             :: jp_cfc          !: number of CFC passive tracers  
    2626   INTEGER, PUBLIC             :: jp_my_trc       !: number of passive tracers in MY_TRC model 
     27   INTEGER, PUBLIC             :: jp_bgc          !: number of passive tracers for the BGC model 
     28 
     29   INTEGER, PUBLIC             :: jp_dia3d        !: number of 3D diagnostic variables 
     30   INTEGER, PUBLIC             :: jp_dia2d        !: number of 2D diagnostic variables 
    2731 
    2832   LOGICAL, PUBLIC             :: ln_pisces       !: PISCES flag  
     
    3438   LOGICAL, PUBLIC             :: ln_my_trc       !: MY_TRC flag  
    3539 
    36  
    37    INTEGER, PUBLIC             :: jp_bgc          !: number of passive tracers for the BGC model 
    38  
    3940   REAL(wp), PUBLIC            :: rtrn  = 0.5 * EPSILON( 1.e0 )    !: truncation value 
    4041 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r7162 r7198  
    7272   REAL(wp)            , PUBLIC                                    ::  rdttrc         !: passive tracer time step 
    7373   REAL(wp)            , PUBLIC                                    ::  r2dttrc        !: = 2*rdttrc except at nit000 (=rdttrc) if neuler=0 
    74    LOGICAL             , PUBLIC                                    ::  ln_top_euler  !: boolean term for euler integration  
     74   LOGICAL             , PUBLIC                                    ::  ln_top_euler   !: boolean term for euler integration  
    7575   LOGICAL             , PUBLIC                                    ::  ln_trcdta      !: Read inputs data from files 
    7676   LOGICAL             , PUBLIC                                    ::  ln_trcdmp      !: internal damping flag 
    7777   LOGICAL             , PUBLIC                                    ::  ln_trcdmp_clo  !: internal damping flag on closed seas 
    78    INTEGER             , PUBLIC                                    ::  nittrc000       !: first time step of passive tracers model 
     78   INTEGER             , PUBLIC                                    ::  nittrc000      !: first time step of passive tracers model 
    7979   LOGICAL             , PUBLIC                                    ::  l_trcdm2dc     !: Diurnal cycle for TOP 
    8080 
     
    114114   END TYPE DIAG 
    115115 
     116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trc3d          !: 3D diagnostics for tracers 
     117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trc2d          !: 2D diagnostics for tracers 
     118 
    116119   !! information for inputs 
    117120   !! -------------------------------------------------- 
     
    120123   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_sbc     !: Use surface boundary condition data 
    121124   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)    ::  ln_trc_cbc     !: Use coastal boundary condition data 
     125   LOGICAL , PUBLIC                                     ::  ln_rnf_ctl     !: remove runoff dilution on tracers 
     126   REAL(wp), PUBLIC                                     ::  rn_bc_time     !: Time scaling factor for SBC and CBC data (seconds in a day) 
    122127 
    123128 
     
    192197      USE lib_mpp, ONLY: ctl_warn 
    193198      !!------------------------------------------------------------------- 
     199      INTEGER :: ierr(3) 
     200      !!------------------------------------------------------------------- 
     201      ierr(:) = 0 
    194202      ! 
    195203      ALLOCATE( trn(jpi,jpj,jpk,jptra), trb(jpi,jpj,jpk,jptra), tra(jpi,jpj,jpk,jptra),       &   
     
    207215         &      trcdta_bdy(jptra,nb_bdy)                                              ,       & 
    208216#endif 
    209          &      STAT = trc_alloc  ) 
    210  
     217         &      STAT = ierr(1)  ) 
     218      ! 
     219      IF (jp_dia3d > 0 ) ALLOCATE( trc3d(jpi,jpj,jpk,jp_dia3d), STAT = ierr(2) ) 
     220      ! 
     221      IF (jp_dia2d > 0 ) ALLOCATE( trc2d(jpi,jpj,jpk,jp_dia2d), STAT = ierr(3) ) 
     222      !  
     223      trc_alloc = MAXVAL( ierr ) 
    211224      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays') 
    212225      ! 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/trcbc.F90

    r6140 r7198  
    44   !! TOP :  module for passive tracer boundary conditions 
    55   !!===================================================================== 
    6    !! History :  3.5 !  2014-04  (M. Vichi, T. Lovato)  Original 
    7    !!            3.6 !  2015-03  (T . Lovato) Revision and BDY support 
     6   !! History :  3.5 !  2014 (M. Vichi, T. Lovato)  Original 
     7   !!            3.6 !  2015 (T . Lovato) Revision and BDY support 
     8   !!            4.0 !  2016 (T . Lovato) Include application of sbc and cbc 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_top 
     
    1112   !!   'key_top'                                                TOP model  
    1213   !!---------------------------------------------------------------------- 
    13    !!   trc_bc       : read and time interpolated tracer Boundary Conditions 
     14   !!   trc_bc       :  Apply tracer Boundary Conditions 
    1415   !!---------------------------------------------------------------------- 
    1516   USE par_trc       !  passive tracers parameters 
     
    2627   PRIVATE 
    2728 
    28    PUBLIC   trc_bc_init    ! called in trcini.F90  
    29    PUBLIC   trc_bc_read    ! called in trcstp.F90 or within 
     29   PUBLIC   trc_bc         ! called in trcstp.F90 or within TOP modules 
     30   PUBLIC   trc_bc_ini     ! called in trcini.F90  
    3031 
    3132   INTEGER  , SAVE, PUBLIC                             :: nb_trcobc    ! number of tracers with open BC 
     
    4344   TYPE(MAP_POINTER), ALLOCATABLE, DIMENSION(:) :: nbmap_ptr   ! array of pointers to nbmap 
    4445 
    45    !!---------------------------------------------------------------------- 
    46    !! NEMO/OPA 3.6 , NEMO Consortium (2015) 
     46   !! * Substitutions 
     47#  include "vectopt_loop_substitute.h90" 
     48   !!---------------------------------------------------------------------- 
     49   !! NEMO/TOP 4.0 , NEMO Consortium (2016) 
    4750   !! $Id$ 
    4851   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    5053CONTAINS 
    5154 
    52    SUBROUTINE trc_bc_init( ntrc ) 
     55   SUBROUTINE trc_bc_ini( ntrc ) 
    5356      !!---------------------------------------------------------------------- 
    54       !!                   ***  ROUTINE trc_bc_init  *** 
     57      !!                   ***  ROUTINE trc_bc_ini  *** 
    5558      !!                     
    5659      !! ** Purpose :   initialisation of passive tracer BC data  
     
    7780      REAL(wp)   , DIMENSION(jpmaxtrc) :: rn_trcfac    ! multiplicative factor for tracer values 
    7881      !! 
    79       NAMELIST/namtrc_bc/ cn_dir_sbc, cn_dir_cbc, cn_dir_obc, sn_trcobc, rn_trofac, sn_trcsbc, rn_trsfac, sn_trccbc, rn_trcfac 
     82      NAMELIST/namtrc_bc/ cn_dir_obc, sn_trcobc, rn_trofac, cn_dir_sbc, sn_trcsbc, rn_trsfac, &  
     83                        & cn_dir_cbc, sn_trccbc, rn_trcfac, ln_rnf_ctl, rn_bc_time 
    8084#if defined key_bdy 
    8185      NAMELIST/namtrc_bdy/ cn_trc_dflt, cn_trc, nn_trcdmp_bdy 
    8286#endif 
    8387      !!---------------------------------------------------------------------- 
    84       IF( nn_timing == 1 )  CALL timing_start('trc_bc_init') 
     88      IF( nn_timing == 1 )  CALL timing_start('trc_bc_ini') 
    8589      ! 
    8690      IF( lwp ) THEN 
    8791         WRITE(numout,*) ' ' 
    88          WRITE(numout,*) 'trc_bc_init : Tracers Boundary Conditions (BC)' 
     92         WRITE(numout,*) 'trc_bc_ini : Tracers Boundary Conditions (BC)' 
    8993         WRITE(numout,*) '~~~~~~~~~~~ ' 
    9094      ENDIF 
     
    9397      ALLOCATE( slf_i(ntrc), STAT=ierr0 ) 
    9498      IF( ierr0 > 0 ) THEN 
    95          CALL ctl_stop( 'trc_bc_init: unable to allocate local slf_i' )   ;   RETURN 
     99         CALL ctl_stop( 'trc_bc_ini: unable to allocate local slf_i' )   ;   RETURN 
    96100      ENDIF 
    97101 
     
    99103      ALLOCATE( n_trc_indobc(ntrc), STAT=ierr0 ) 
    100104      IF( ierr0 > 0 ) THEN 
    101          CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indobc' )   ;   RETURN 
     105         CALL ctl_stop( 'trc_bc_ini: unable to allocate n_trc_indobc' )   ;   RETURN 
    102106      ENDIF 
    103107      nb_trcobc      = 0 
     
    106110      ALLOCATE( n_trc_indsbc(ntrc), STAT=ierr0 ) 
    107111      IF( ierr0 > 0 ) THEN 
    108          CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indsbc' )   ;   RETURN 
     112         CALL ctl_stop( 'trc_bc_ini: unable to allocate n_trc_indsbc' )   ;   RETURN 
    109113      ENDIF 
    110114      nb_trcsbc      = 0 
     
    113117      ALLOCATE( n_trc_indcbc(ntrc), STAT=ierr0 ) 
    114118      IF( ierr0 > 0 ) THEN 
    115          CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indcbc' )   ;   RETURN 
     119         CALL ctl_stop( 'trc_bc_ini: unable to allocate n_trc_indcbc' )   ;   RETURN 
    116120      ENDIF 
    117121      nb_trccbc      = 0 
     
    140144      DO jn = 1, ntrc 
    141145         DO ib = 1, nb_bdy 
    142             ! Set type of obc in BDY data structure (around here we may plug user override of obc type from nml) 
     146            ! Set type of obc in BDY data structure (TL: around here we may plug user override of obc type from nml) 
    143147            IF ( ln_trc_obc(jn) ) THEN 
    144148               trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc(ib) ) 
     
    195199         ENDIF 
    196200         WRITE(numout,'(2a)') '   COASTAL BC data repository : ', TRIM(cn_dir_cbc) 
    197  
     201         IF ( .NOT. ln_rnf ) ln_rnf_ctl = .FALSE. 
     202         IF ( ln_rnf_ctl )  WRITE(numout,'(a)') ' -> Remove runoff dilution effect on tracers with absent river load (ln_rnf_ctl = .TRUE.)'  
    198203         WRITE(numout,*) ' ' 
    199204         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with OPEN BCs data:', nb_trcobc 
     
    230235         ALLOCATE ( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), nbmap_ptr(nb_trcobc), STAT=ierr1 ) 
    231236         IF( ierr1 > 0 ) THEN 
    232             CALL ctl_stop( 'trc_bc_init: unable to allocate sf_trcobc structure' )   ;   RETURN 
     237            CALL ctl_stop( 'trc_bc_ini: unable to allocate sf_trcobc structure' )   ;   RETURN 
    233238         ENDIF 
    234239 
     
    248253                  IF( sn_trcobc(jn)%ln_tint )  ALLOCATE( sf_trcobc(jl)%fdta(nblen,1,jpk,2) , STAT=ierr3 ) 
    249254                  IF( ierr2 + ierr3 > 0 ) THEN 
    250                     CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer OBC data arrays' )   ;   RETURN 
     255                    CALL ctl_stop( 'trc_bc_ini : unable to allocate passive tracer OBC data arrays' )   ;   RETURN 
    251256                  ENDIF 
    252257                  trcdta_bdy(jn,ib)%trc => sf_trcobc(jl)%fnow(:,1,:) 
     
    270275         ENDDO 
    271276 
    272          CALL fld_fill( sf_trcobc, slf_i, cn_dir_obc, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' ) 
     277         CALL fld_fill( sf_trcobc, slf_i, cn_dir_obc, 'trc_bc_ini', 'Passive tracer OBC data', 'namtrc_bc' ) 
    273278      ENDIF 
    274279#endif 
     
    277282         ALLOCATE( sf_trcsbc(nb_trcsbc), rf_trsfac(nb_trcsbc), STAT=ierr1 ) 
    278283         IF( ierr1 > 0 ) THEN 
    279             CALL ctl_stop( 'trc_bc_init: unable to allocate  sf_trcsbc structure' )   ;   RETURN 
     284            CALL ctl_stop( 'trc_bc_ini: unable to allocate  sf_trcsbc structure' )   ;   RETURN 
    280285         ENDIF 
    281286         ! 
     
    288293               IF( sn_trcsbc(jn)%ln_tint )  ALLOCATE( sf_trcsbc(jl)%fdta(jpi,jpj,1,2) , STAT=ierr3 ) 
    289294               IF( ierr2 + ierr3 > 0 ) THEN 
    290                  CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer SBC data arrays' )   ;   RETURN 
     295                 CALL ctl_stop( 'trc_bc_ini : unable to allocate passive tracer SBC data arrays' )   ;   RETURN 
    291296               ENDIF 
    292297            ENDIF 
     
    294299         ENDDO 
    295300         !                         ! fill sf_trcsbc with slf_i and control print 
    296          CALL fld_fill( sf_trcsbc, slf_i, cn_dir_sbc, 'trc_bc_init', 'Passive tracer SBC data', 'namtrc_bc' ) 
     301         CALL fld_fill( sf_trcsbc, slf_i, cn_dir_sbc, 'trc_bc_ini', 'Passive tracer SBC data', 'namtrc_bc' ) 
    297302         ! 
    298303      ENDIF 
     
    319324         ENDDO 
    320325         !                         ! fill sf_trccbc with slf_i and control print 
    321          CALL fld_fill( sf_trccbc, slf_i, cn_dir_cbc, 'trc_bc_init', 'Passive tracer CBC data', 'namtrc_bc' ) 
     326         CALL fld_fill( sf_trccbc, slf_i, cn_dir_cbc, 'trc_bc_ini', 'Passive tracer CBC data', 'namtrc_bc' ) 
    322327         ! 
    323328      ENDIF 
    324329      ! 
    325330      DEALLOCATE( slf_i )          ! deallocate local field structure 
    326       IF( nn_timing == 1 )  CALL timing_stop('trc_bc_init') 
    327       ! 
    328    END SUBROUTINE trc_bc_init 
    329  
    330  
    331    SUBROUTINE trc_bc_read(kt, jit) 
     331      IF( nn_timing == 1 )  CALL timing_stop('trc_bc_ini') 
     332      ! 
     333   END SUBROUTINE trc_bc_ini 
     334 
     335 
     336   SUBROUTINE trc_bc(kt, jit) 
    332337      !!---------------------------------------------------------------------- 
    333       !!                   ***  ROUTINE trc_bc_init  *** 
     338      !!                   ***  ROUTINE trc_bc  *** 
    334339      !! 
    335       !! ** Purpose :  Read passive tracer Boundary Conditions data 
     340      !! ** Purpose :  Apply Boundary Conditions data to tracers 
    336341      !! 
    337       !! ** Method  :  Read BC inputs and update data structures using fldread 
     342      !! ** Method  :  1) Read BC inputs and update data structures using fldread 
     343      !!               2) Apply Boundary Conditions to tracers 
    338344      !!               
    339345      !!---------------------------------------------------------------------- 
     
    341347       
    342348      !! * Arguments 
    343       INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     349      INTEGER, INTENT( in ) ::   kt              ! ocean time-step index 
    344350      INTEGER, INTENT( in ), OPTIONAL ::   jit   ! subcycle time-step index (for timesplitting option) 
     351      !! 
     352      INTEGER  :: ji, jj, jk, jn, jl             ! Loop index 
     353      REAL(wp) :: zfact, zrnf 
    345354      !!--------------------------------------------------------------------- 
    346355      ! 
    347       IF( nn_timing == 1 )  CALL timing_start('trc_bc_read') 
     356      IF( nn_timing == 1 )  CALL timing_start('trc_bc') 
    348357 
    349358      IF( kt == nit000 .AND. lwp) THEN 
    350359         WRITE(numout,*) 
    351          WRITE(numout,*) 'trc_bc_read : Surface boundary conditions for passive tracers.' 
     360         WRITE(numout,*) 'trc_bc : Surface boundary conditions for passive tracers.' 
    352361         WRITE(numout,*) '~~~~~~~~~~~ ' 
    353362      ENDIF 
    354363 
     364      ! 1. Update Boundary conditions data 
    355365      IF ( PRESENT(jit) ) THEN  
    356366 
     
    395405      ENDIF 
    396406 
    397       ! 
    398       IF( nn_timing == 1 )  CALL timing_stop('trc_bc_read') 
    399       ! 
    400    END SUBROUTINE trc_bc_read 
     407      ! 2. Apply Boundary conditions data 
     408      !  
     409      DO jn = 1 , jptra 
     410         ! 
     411         ! Remove river dilution for tracers with absent river load 
     412         IF ( ln_rnf_ctl .AND. .NOT. ln_trc_cbc(jn) ) THEN 
     413            DO jj = 2, jpj 
     414               DO ji = fs_2, fs_jpim1 
     415                  DO jk = 1, nk_rnf(ji,jj) 
     416                     zrnf = (rnf(ji,jj) + rnf_b(ji,jj)) * 0.5_wp * r1_rau0 / h_rnf(ji,jj) 
     417                     tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn)  + (trn(ji,jj,jk,jn) * zrnf) 
     418                  ENDDO 
     419               ENDDO 
     420            ENDDO 
     421         ENDIF 
     422           
     423         ! OPEN boundary conditions: trcbdy is called in trcnxt ! 
     424 
     425         ! SURFACE boundary conditions 
     426         IF (ln_trc_sbc(jn)) THEN 
     427            jl = n_trc_indsbc(jn) 
     428            DO jj = 2, jpj 
     429               DO ji = fs_2, fs_jpim1   ! vector opt. 
     430                  zfact = 1. / ( e3t_n(ji,jj,1) * rn_bc_time ) 
     431                  tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + rf_trsfac(jl) * sf_trcsbc(jl)%fnow(ji,jj,1) * zfact 
     432               END DO 
     433            END DO 
     434         END IF 
     435 
     436         ! COASTAL boundary conditions 
     437         IF ( ln_rnf .AND. ln_trc_cbc(jn)) THEN 
     438            jl = n_trc_indcbc(jn) 
     439            DO jj = 2, jpj 
     440               DO ji = fs_2, fs_jpim1   ! vector opt. 
     441                  DO jk = 1, nk_rnf(ji,jj) 
     442                     zfact = rn_rfact / ( e1e2t(ji,jj) * h_rnf(ji,jj) * rn_bc_time )  
     443                     tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + rf_trcfac(jl) * sf_trccbc(jl)%fnow(ji,jj,1) * zfact 
     444                  ENDDO 
     445               END DO 
     446            END DO 
     447         END IF 
     448         !                                                       ! =========== 
     449      END DO                                                     ! tracer loop 
     450      !                                                          ! =========== 
     451      ! 
     452      IF( nn_timing == 1 )  CALL timing_stop('trc_bc') 
     453      ! 
     454   END SUBROUTINE trc_bc 
    401455 
    402456#else 
     
    406460CONTAINS 
    407461 
    408    SUBROUTINE trc_bc_init( ntrc )        ! Empty routine 
     462   SUBROUTINE trc_bc_ini( ntrc )        ! Empty routine 
    409463      INTEGER,INTENT(IN) :: ntrc                           ! number of tracers 
    410       WRITE(*,*) 'trc_bc_init: You should not have seen this print! error?', kt 
    411    END SUBROUTINE trc_bc_init 
    412  
    413    SUBROUTINE trc_bc_read( kt )        ! Empty routine 
    414       WRITE(*,*) 'trc_bc_read: You should not have seen this print! error?', kt 
    415    END SUBROUTINE trc_bc_read 
     464      WRITE(*,*) 'trc_bc_ini: You should not have seen this print! error?', kt 
     465   END SUBROUTINE trc_bc_ini 
     466 
     467   SUBROUTINE trc_bc( kt )        ! Empty routine 
     468      WRITE(*,*) 'trc_bc: You should not have seen this print! error?', kt 
     469   END SUBROUTINE trc_bc 
    416470#endif 
    417471 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/trcdta.F90

    r6701 r7198  
    99   !!            3.4   !  2010-11  (C. Ethe, G. Madec)  use of fldread + dynamical allocation  
    1010   !!            3.5   !  2013-08  (M. Vichi)  generalization for other BGC models 
    11    !!            3.6   !  2015-03  (T. Lovato) revision of code log info 
     11   !!            3.6   !  2015-03  (T. Lovato) revisit code I/O 
    1212   !!---------------------------------------------------------------------- 
    1313#if defined key_top  
     
    2828 
    2929   PUBLIC   trc_dta         ! called in trcini.F90 and trcdmp.F90 
    30    PUBLIC   trc_dta_init    ! called in trcini.F90  
     30   PUBLIC   trc_dta_ini     ! called in trcini.F90  
    3131 
    3232   INTEGER  , SAVE, PUBLIC                             :: nb_trcdta   ! number of tracers to be initialised with data 
     
    4545CONTAINS 
    4646 
    47    SUBROUTINE trc_dta_init(ntrc) 
    48       !!---------------------------------------------------------------------- 
    49       !!                   ***  ROUTINE trc_dta_init  *** 
     47   SUBROUTINE trc_dta_ini(ntrc) 
     48      !!---------------------------------------------------------------------- 
     49      !!                   ***  ROUTINE trc_dta_ini  *** 
    5050      !!                     
    5151      !! ** Purpose :   initialisation of passive tracer input data  
     
    7070      !!---------------------------------------------------------------------- 
    7171      ! 
    72       IF( nn_timing == 1 )  CALL timing_start('trc_dta_init') 
     72      IF( nn_timing == 1 )  CALL timing_start('trc_dta_ini') 
    7373      ! 
    7474      IF( lwp ) THEN 
    7575         WRITE(numout,*) ' ' 
    76          WRITE(numout,*) '  trc_dta_init : Tracers Initial Conditions (IC)' 
     76         WRITE(numout,*) '  trc_dta_ini : Tracers Initial Conditions (IC)' 
    7777         WRITE(numout,*) '  ~~~~~~~~~~~ ' 
    7878      ENDIF 
     
    8383      ALLOCATE( n_trc_index(ntrc), slf_i(ntrc), STAT=ierr0 ) 
    8484      IF( ierr0 > 0 ) THEN 
    85          CALL ctl_stop( 'trc_dta_init: unable to allocate n_trc_index' )   ;   RETURN 
     85         CALL ctl_stop( 'trc_dta_ini: unable to allocate n_trc_index' )   ;   RETURN 
    8686      ENDIF 
    8787      nb_trcdta      = 0 
     
    103103      REWIND( numnat_ref )              ! Namelist namtrc_dta in reference namelist : Passive tracer input data 
    104104      READ  ( numnat_ref, namtrc_dta, IOSTAT = ios, ERR = 901) 
    105 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta_init in reference namelist', lwp ) 
     105901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta_ini in reference namelist', lwp ) 
    106106 
    107107      REWIND( numnat_cfg )              ! Namelist namtrc_dta in configuration namelist : Passive tracer input data 
    108108      READ  ( numnat_cfg, namtrc_dta, IOSTAT = ios, ERR = 902 ) 
    109 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta_init in configuration namelist', lwp ) 
     109902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta_ini in configuration namelist', lwp ) 
    110110      IF(lwm) WRITE ( numont, namtrc_dta ) 
    111111 
     
    118118               zfact  = rn_trfac(jn) 
    119119               IF( clndta /=  clntrc ) THEN  
    120                   CALL ctl_warn( 'trc_dta_init: passive tracer data initialisation    ',   & 
     120                  CALL ctl_warn( 'trc_dta_ini: passive tracer data initialisation    ',   & 
    121121                  &              'Input name of data file : '//TRIM(clndta)//   & 
    122122                  &              ' differs from that of tracer : '//TRIM(clntrc)//' ') 
     
    132132         ALLOCATE( sf_trcdta(nb_trcdta), rf_trfac(nb_trcdta), STAT=ierr1 ) 
    133133         IF( ierr1 > 0 ) THEN 
    134             CALL ctl_stop( 'trc_dta_init: unable to allocate  sf_trcdta structure' )   ;   RETURN 
     134            CALL ctl_stop( 'trc_dta_ini: unable to allocate  sf_trcdta structure' )   ;   RETURN 
    135135         ENDIF 
    136136         ! 
     
    143143               IF( sn_trcdta(jn)%ln_tint )  ALLOCATE( sf_trcdta(jl)%fdta(jpi,jpj,jpk,2) , STAT=ierr3 ) 
    144144               IF( ierr2 + ierr3 > 0 ) THEN 
    145                  CALL ctl_stop( 'trc_dta_init : unable to allocate passive tracer data arrays' )   ;   RETURN 
     145                 CALL ctl_stop( 'trc_dta_ini : unable to allocate passive tracer data arrays' )   ;   RETURN 
    146146               ENDIF 
    147147            ENDIF 
     
    149149         ENDDO 
    150150         !                         ! fill sf_trcdta with slf_i and control print 
    151          CALL fld_fill( sf_trcdta, slf_i, cn_dir, 'trc_dta_init', 'Passive tracer data', 'namtrc' ) 
     151         CALL fld_fill( sf_trcdta, slf_i, cn_dir, 'trc_dta_ini', 'Passive tracer data', 'namtrc' ) 
    152152         ! 
    153153      ENDIF 
    154154      ! 
    155155      DEALLOCATE( slf_i )          ! deallocate local field structure 
    156       IF( nn_timing == 1 )  CALL timing_stop('trc_dta_init') 
    157       ! 
    158    END SUBROUTINE trc_dta_init 
    159  
    160  
    161    SUBROUTINE trc_dta( kt, sf_trcdta, ptrfac, ptrc) 
     156      IF( nn_timing == 1 )  CALL timing_stop('trc_dta_ini') 
     157      ! 
     158   END SUBROUTINE trc_dta_ini 
     159 
     160 
     161   SUBROUTINE trc_dta( kt, sf_trcdta, ztrcfac, ztrcdta) 
    162162      !!---------------------------------------------------------------------- 
    163163      !!                   ***  ROUTINE trc_dta  *** 
     
    169169      !!              - ln_trcdmp=F: deallocates the data structure as they are not used 
    170170      !! 
    171       !! ** Action  :   sf_trcdta   passive tracer data on medl mesh and interpolated at time-step kt 
    172       !!---------------------------------------------------------------------- 
    173       INTEGER                     , INTENT(in   ) ::   kt     ! ocean time-step 
    174       TYPE(FLD), DIMENSION(1)     , INTENT(inout) ::   sf_trcdta     ! array of information on the field to read 
    175       REAL(wp)                    , INTENT(in   ) ::   ptrfac  ! multiplication factor 
    176       REAL(wp), DIMENSION(jpi,jpj,jpk), OPTIONAL  , INTENT(out  ) ::   ptrc 
     171      !! ** Action  :   sf_trcdta   passive tracer data on meld mesh and interpolated at time-step kt 
     172      !!---------------------------------------------------------------------- 
     173      INTEGER                          , INTENT(in   )   ::   kt         ! ocean time-step 
     174      TYPE(FLD), DIMENSION(1)          , INTENT(inout)   ::   sf_trcdta  ! array of information on the field to read 
     175      REAL(wp)                         , INTENT(in   )   ::   ztrcfac    ! multiplication factor 
     176      REAL(wp),  DIMENSION(jpi,jpj,jpk), INTENT(inout  ) ::   ztrcdta    ! 3D data array 
    177177      ! 
    178178      INTEGER ::   ji, jj, jk, jl, jkk, ik    ! dummy loop indices 
    179179      REAL(wp)::   zl, zi 
    180180      REAL(wp), DIMENSION(jpk) ::  ztp                ! 1D workspace 
    181       REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 3D  workspace 
    182181      CHARACTER(len=100) :: clndta 
    183182      !!---------------------------------------------------------------------- 
     
    187186      IF( nb_trcdta > 0 ) THEN 
    188187         ! 
    189          CALL wrk_alloc( jpi, jpj, jpk, ztrcdta )    ! Memory allocation 
    190          ! 
    191          CALL fld_read( kt, 1, sf_trcdta )      !==   read data at kt time step   ==! 
    192          ztrcdta(:,:,:) = sf_trcdta(1)%fnow(:,:,:) * tmask(:,:,:)    ! Mask 
    193          ! 
    194          IF( ln_sco ) THEN                   !==   s- or mixed s-zps-coordinate   ==! 
     188         ! read data at kt time step 
     189         CALL fld_read( kt, 1, sf_trcdta ) 
     190         ztrcdta(:,:,:) = sf_trcdta(1)%fnow(:,:,:) * tmask(:,:,:) 
     191         !  
     192         IF( ln_sco ) THEN                !== s- or mixed s-zps-coordinate  ==! 
    195193            ! 
    196194            IF( kt == nit000 .AND. lwp )THEN 
     
    205203                        ztp(jk) = ztrcdta(ji,jj,1) 
    206204                     ELSEIF( zl > gdept_1d(jpk) ) THEN         ! below the last level of data 
    207                         ztp(jk) =  ztrcdta(ji,jj,jpkm1) 
     205                        ztp(jk) = ztrcdta(ji,jj,jpkm1) 
    208206                     ELSE                                      ! inbetween : vertical interpolation between jkk & jkk+1 
    209207                        DO jkk = 1, jpkm1                                  ! when  gdept(jkk) < zl < gdept(jkk+1) 
    210208                           IF( (zl-gdept_1d(jkk)) * (zl-gdept_1d(jkk+1)) <= 0._wp ) THEN 
    211209                              zi = ( zl - gdept_1d(jkk) ) / (gdept_1d(jkk+1)-gdept_1d(jkk)) 
    212                               ztp(jk) = ztrcdta(ji,jj,jkk) + ( ztrcdta(ji,jj,jkk+1) - & 
    213                                         ztrcdta(ji,jj,jkk) ) * zi  
     210                              ztp(jk) = ztrcdta(ji,jj,jkk) + ( ztrcdta(ji,jj,jkk+1) - ztrcdta(ji,jj,jkk) ) * zi 
    214211                           ENDIF 
    215212                        END DO 
     
    217214                  END DO 
    218215                  DO jk = 1, jpkm1 
    219                     ztrcdta(ji,jj,jk) = ztp(jk) * tmask(ji,jj,jk)     ! mask required for mixed zps-s-coord 
     216                     ztrcdta(ji,jj,jk) = ztp(jk) * tmask(ji,jj,jk)     ! mask required for mixed zps-s-coord 
    220217                  END DO 
    221218                  ztrcdta(ji,jj,jpk) = 0._wp 
     
    224221            !  
    225222         ELSE                                !==   z- or zps- coordinate   ==! 
    226             ! 
    227             IF( ln_zps ) THEN                      ! zps-coordinate (partial steps) interpolation at the last ocean level 
     223            ! zps-coordinate (partial steps) interpolation at the last ocean level 
     224            IF( ln_zps ) THEN 
    228225               DO jj = 1, jpj 
    229226                  DO ji = 1, jpi 
     
    244241         ENDIF 
    245242         ! 
    246          ! Add multiplicative factor 
    247          ztrcdta(:,:,:) = ztrcdta(:,:,:) * ptrfac 
    248          ! 
    249          ! Data structure for trc_ini (and BFMv5.1 coupling) 
    250          IF( .NOT. PRESENT(ptrc) ) sf_trcdta(1)%fnow(:,:,:) = ztrcdta(:,:,:) 
    251          ! 
    252          ! Data structure for trc_dmp 
    253          IF( PRESENT(ptrc) )  ptrc(:,:,:) = ztrcdta(:,:,:) 
    254          ! 
    255          CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta ) 
     243         ! Scale by multiplicative factor 
     244         ztrcdta(:,:,:) = ztrcdta(:,:,:) * ztrcfac 
    256245         ! 
    257246      ENDIF 
     
    266255   !!---------------------------------------------------------------------- 
    267256CONTAINS 
    268    SUBROUTINE trc_dta( kt, sf_trcdta, ptrfac, ptrc)        ! Empty routine 
     257   SUBROUTINE trc_dta( kt, sf_trcdta, ztrcfac, ztrcdta)        ! Empty routine 
    269258      WRITE(*,*) 'trc_dta: You should not have seen this print! error?', kt 
    270259   END SUBROUTINE trc_dta 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r7162 r7198  
    2525   USE lib_mpp         ! distribued memory computing library 
    2626   USE trcice          ! tracers in sea ice 
    27    USE trcbc,   only : trc_bc_init ! generalized Boundary Conditions 
     27   USE trcbc,   only : trc_bc_ini ! generalized Boundary Conditions 
    2828  
    2929   IMPLICIT NONE 
     
    224224      ! 
    225225      ! Initialisation of tracers Initial Conditions 
    226       IF( ln_trcdta )      CALL trc_dta_init(jptra) 
     226      IF( ln_trcdta )      CALL trc_dta_ini(jptra) 
    227227 
    228228      ! Initialisation of tracers Boundary Conditions 
    229       IF( ln_my_trc )     CALL trc_bc_init(jptra) 
     229      IF( ln_my_trc )     CALL trc_bc_ini(jptra) 
    230230 
    231231      IF( ln_rsttr ) THEN 
     
    234234        ! 
    235235      ELSE 
    236         ! 
    237         IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping 
    238             ! 
     236        ! Initialisation of tracer from a file that may also be used for damping 
     237        IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN 
     238            ! update passive tracers arrays with input data read from file 
    239239            DO jn = 1, jptra 
    240                IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
     240               IF( ln_trc_ini(jn) ) THEN 
    241241                  jl = n_trc_index(jn)  
    242                   CALL trc_dta( nit000, sf_trcdta(jl), rf_trfac(jl) )   ! read tracer data at nit000 
    243                   trn(:,:,:,jn) = sf_trcdta(jl)%fnow(:,:,:)  
     242                  CALL trc_dta( nit000, sf_trcdta(jl), rf_trfac(jl), trn(:,:,:,jn) ) 
    244243                  ! 
    245                   IF( .NOT.ln_trcdmp .AND. .NOT.ln_trcdmp_clo ) THEN      !== deallocate data structure   ==! 
    246                      !                                                    (data used only for initialisation) 
     244                  ! deallocate data structure if data are not used for damping 
     245                  IF( .NOT.ln_trcdmp .AND. .NOT.ln_trcdmp_clo ) THEN 
    247246                     IF(lwp) WRITE(numout,*) 'trc_dta: deallocate data arrays as they are only used to initialize the run' 
    248                                                   DEALLOCATE( sf_trcdta(jl)%fnow )     !  arrays in the structure 
     247                                                  DEALLOCATE( sf_trcdta(jl)%fnow ) 
    249248                     IF( sf_trcdta(jl)%ln_tint )  DEALLOCATE( sf_trcdta(jl)%fdta ) 
    250249                     ! 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r7124 r7198  
    145145      INTEGER  ::   ios, ierr, icfc       ! Local integer output status for namelist read 
    146146      !! 
    147       NAMELIST/namtrc/jptra, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_c14, & 
    148          &            sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo 
     147      NAMELIST/namtrc/jp_bgc, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_c14, & 
     148         &            sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo, jp_dia3d, jp_dia2d 
    149149      !!--------------------------------------------------------------------- 
    150150      ! Dummy settings to fill tracers data structure 
     
    167167      ! Control settings 
    168168      IF( ln_pisces .AND. ln_my_trc )   CALL ctl_stop( 'Choose only ONE BGC model - PISCES or MY_TRC' ) 
    169       IF( .NOT. ln_pisces .AND. .NOT. ln_my_trc )   jptra = 0 
     169      IF( .NOT. ln_pisces .AND. .NOT. ln_my_trc )   jp_bgc = 0 
    170170      ll_cfc = ln_cfc11 .OR. ln_cfc12 
    171171      ! 
     172      jptra       =  0 
    172173      jp_pisces   =  0    ;   jp_pcs0  =  0    ;   jp_pcs1  = 0 
    173174      jp_my_trc   =  0    ;   jp_myt0  =  0    ;   jp_myt1  = 0 
    174175      jp_cfc      =  0    ;   jp_cfc0  =  0    ;   jp_cfc1  = 0 
    175       jp_age      =  0    ;   jp_c14   = 0 
     176      jp_age      =  0    ;   jp_c14   =  0 
    176177      ! 
    177178      IF( ln_pisces )  THEN 
    178          jp_pisces = jptra 
     179         jp_pisces = jp_bgc 
    179180         jp_pcs0   = 1 
    180181         jp_pcs1   = jp_pisces 
    181182      ENDIF 
    182183      IF( ln_my_trc )  THEN 
    183           jp_my_trc = jptra 
     184          jp_my_trc = jp_bgc 
    184185          jp_myt0   = 1 
    185186          jp_myt1   = jp_my_trc 
    186187      ENDIF 
    187188      ! 
    188       jp_bgc  =   jptra 
     189      jptra  = jp_bgc 
    189190      ! 
    190191      IF( ln_age )    THEN 
     
    210211         WRITE(numout,*) ' Namelist : namtrc' 
    211212         WRITE(numout,*) '   Total number of passive tracers              jptra         = ', jptra 
     213         WRITE(numout,*) '   Total number of BGC tracers                  jp_bgc        = ', jp_bgc 
    212214         WRITE(numout,*) '   Simulating PISCES model                      ln_pisces     = ', ln_pisces 
    213215         WRITE(numout,*) '   Simulating MY_TRC  model                     ln_my_trc     = ', ln_my_trc 
     
    219221         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp 
    220222         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo 
    221          WRITE(numout,*) '   Total number of BGC-like tracers             jp_bgc        = ', jp_bgc 
    222223         WRITE(numout,*) ' ' 
    223224         WRITE(numout,*) ' ' 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/SETTE/sette.sh

    r6460 r7198  
    306306#   set_namelist namelist_cfg nn_solv 2 
    307307    set_namelist namelist_top_cfg ln_trcdta .false. 
    308     set_namelist namelist_top_cfg ln_diatrc .false. 
    309308    # put ln_ironsed, ln_river, ln_ndepo, ln_dust to false 
    310309    # if not you need input files, and for tests is not necessary 
     
    341340    set_namelist namelist_cfg jpnij 8 
    342341#   set_namelist namelist_cfg nn_solv 2 
    343     set_namelist namelist_top_cfg ln_diatrc .false. 
    344342    set_namelist namelist_top_cfg ln_rsttr .true. 
    345343    set_namelist namelist_top_cfg nn_rsttr 2 
     
    400398#   set_namelist namelist_cfg nn_solv 2 
    401399    set_namelist namelist_top_cfg ln_trcdta .false. 
    402     set_namelist namelist_top_cfg ln_diatrc .false. 
    403400    # put ln_ironsed, ln_river, ln_ndepo, ln_dust to false 
    404401    # if not you need input files, and for tests is not necessary 
     
    439436#   set_namelist namelist_cfg nn_solv 2 
    440437    set_namelist namelist_top_cfg ln_trcdta .false. 
    441     set_namelist namelist_top_cfg ln_diatrc .false. 
    442438    # put ln_ironsed, ln_river, ln_ndepo, ln_dust to false 
    443439    # if not you need input files, and for tests is not necessary 
     
    486482    set_namelist namelist_cfg jpnij 8 
    487483    set_namelist namelist_top_cfg ln_trcdta .false. 
    488     set_namelist namelist_top_cfg ln_diatrc .false. 
    489484    # put ln_ironsed, ln_river, ln_ndepo, ln_dust to false 
    490485    # if not you need input files, and for tests is not necessary 
     
    519514    set_namelist namelist_cfg jpnj 4 
    520515    set_namelist namelist_cfg jpnij 8 
    521     set_namelist namelist_top_cfg ln_diatrc .false. 
    522516    set_namelist namelist_top_cfg ln_rsttr .true. 
    523517    set_namelist namelist_top_cfg nn_rsttr 2 
     
    572566    set_namelist namelist_cfg jpnij 16 
    573567    set_namelist namelist_top_cfg ln_trcdta .false. 
    574     set_namelist namelist_top_cfg ln_diatrc .false. 
    575568    # put ln_ironsed, ln_river, ln_ndepo, ln_dust to false 
    576569    # if not you need input files, and for tests is not necessary 
     
    610603    set_namelist namelist_cfg jpnij 16 
    611604    set_namelist namelist_top_cfg ln_trcdta .false. 
    612     set_namelist namelist_top_cfg ln_diatrc .false. 
    613605    # put ln_ironsed, ln_river, ln_ndepo, ln_dust to false 
    614606    # if not you need input files, and for tests is not necessary 
Note: See TracChangeset for help on using the changeset viewer.