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 5160 for branches/2015/dev_r5144_CMCC5_BDY_for_TOP – NEMO

Ignore:
Timestamp:
2015-03-23T15:30:55+01:00 (9 years ago)
Author:
lovato
Message:

First implementation of BDY for TOP component, see #1441 (dev_r5144_CMCC5_BDY_for_TOP).

Location:
branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM
Files:
1 added
12 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/CONFIG/SHARED/namelist_top_ref

    r5102 r5160  
    107107&namtrc_bc 
    108108! 
    109    cn_dir        =  './'      !  root directory for the location of the data files 
     109   cn_dir_sbc        =  './'      !  root directory for the location of SURFACE data files 
     110   cn_dir_cbc        =  './'      !  root directory for the location of COASTAL data files 
     111   cn_dir_obc        =  './'      !  root directory for the location of OPEN data files 
    110112/ 
     113!---------------------------------------------------------------------- 
     114!namtrc_bdy       !   Setup of tracer boundary conditions 
     115!----------------------------------------------------------------------- 
     116$namtrc_bdy 
     117   cn_trc_dflt     =  'neumann'    !  OBC applied by default to all tracers 
     118   cn_trc          =  'none'       !  Boundary conditions appled to the active tracers (see namtrc) 
     119 
     120   nn_trcdmp_bdy   = 0     !  Use damping timescales defined in nambdy of namelist 
     121                           !  = 0 NO damping of tracers at open boudaries 
     122                           !  = 1 Only for tracers forced with external data 
     123                           !  = 2 Damping applied to all tracers 
     124/ 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90

    r4699 r5160  
    7070      REAL, POINTER, DIMENSION(:,:)   ::  ht_i  !: Now ice  thickness climatology 
    7171      REAL, POINTER, DIMENSION(:,:)   ::  ht_s  !: now snow thickness 
     72#endif 
     73#if defined key_top 
     74      CHARACTER(LEN=20)                   :: cn_obc  !: type of boundary condition to apply 
     75      REAL(wp)                            :: rn_fac  !: multiplicative scaling factor 
     76      REAL(wp), POINTER, DIMENSION(:,:)   :: trc     !: now field of the tracer 
     77      LOGICAL                             :: dmp     !: obc damping term 
    7278#endif 
    7379   END TYPE OBC_DATA 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcsms_my_trc.F90

    r4990 r5160  
    1818   USE trd_oce 
    1919   USE trdtrc 
     20   USE trcbc, only : trc_bc_read 
    2021 
    2122   IMPLICIT NONE 
     
    5657      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrmyt ) 
    5758 
    58       WHERE( (glamt <= 170) .AND. (glamt >= 160) .AND. (gphit <= -74) .AND. (gphit >=-75.6) ) 
    59         trn(:,:,1,jpmyt1) = 1._wp 
    60         trb(:,:,1,jpmyt1) = 1._wp 
    61         tra(:,:,1,jpmyt1) = 0._wp 
    62       END WHERE 
     59      CALL trc_bc_read  ( kt )       ! tracers: surface and lateral Boundary Conditions 
    6360 
    64       IF( l_trdtrc ) THEN      ! Save the trends in the ixed layer 
     61      ! add here the call to BGC model 
     62 
     63      ! Save the trends in the mixed layer 
     64      IF( l_trdtrc ) THEN 
    6565          DO jn = jp_myt0, jp_myt1 
    6666            ztrmyt(:,:,:) = tra(:,:,:,jn) 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcwri_my_trc.F90

    r4996 r5160  
    3737      DO jn = jp_myt0, jp_myt1 
    3838         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer 
    39          CALL iom_put( cltra, trn(:,:,:,jn) ) 
     39         IF( ln_trc_wri(jn) ) CALL iom_put( cltra, trn(:,:,:,jn) ) 
    4040      END DO 
    4141      ! 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r5102 r5160  
    318318      END SELECT 
    319319 
    320       IF( .NOT. ln_tradmp )   & 
     320      IF( .NOT. ln_trcdmp )   & 
    321321         &   CALL ctl_stop( 'passive trace damping need key_tradmp to compute damping coef.' ) 
    322322      ! 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r4990 r5160  
    3333   USE trdtra 
    3434   USE tranxt 
     35   USE trcbdy          ! BDY open boundaries 
     36   USE bdy_par, only: lk_bdy 
    3537# if defined key_agrif 
    3638   USE agrif_top_interp 
     
    108110 
    109111 
    110 #if defined key_bdy 
    111 !!      CALL bdy_trc( kt )               ! BDY open boundaries 
    112 #endif 
     112      IF( lk_bdy )  CALL trc_bdy( kt )               ! BDY open boundaries 
     113 
    113114#if defined key_agrif 
    114115      CALL Agrif_trc                   ! AGRIF zoom boundaries 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r5120 r5160  
    2727   USE trcsbc          ! surface boundary condition          (trc_sbc routine) 
    2828   USE zpshde          ! partial step: hor. derivative       (zps_hde routine) 
     29   USE trcbdy          ! BDY open boundaries 
     30   USE bdy_par, only: lk_bdy 
    2931 
    3032#if defined key_agrif 
     
    6870         IF( ln_trcdmp )        CALL trc_dmp( kstp )            ! internal damping trends 
    6971         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kstp )        ! internal damping trends on closed seas only 
     72         IF( lk_bdy )           CALL trc_bdy_dmp( kstp )        ! BDY damping trends 
    7073                                CALL trc_adv( kstp )            ! horizontal & vertical advection  
    7174                                CALL trc_ldf( kstp )            ! lateral mixing 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r4990 r5160  
    1414   USE par_oce 
    1515   USE par_trc 
     16#if defined key_bdy 
     17   USE bdy_oce, only: nb_bdy, OBC_DATA 
     18#endif 
    1619    
    1720   IMPLICIT NONE 
     
    6972       CHARACTER(len = 20)  :: clunit   !: unit 
    7073       LOGICAL              :: llinit   !: read in a file or not 
     74#if defined  key_my_trc 
     75       LOGICAL              :: llsbc   !: read in a file or not 
     76       LOGICAL              :: llcbc   !: read in a file or not 
     77       LOGICAL              :: llobc   !: read in a file or not 
     78#endif 
    7179       LOGICAL              :: llsave   !: save the tracer or not 
    7280   END TYPE PTRACER 
     
    169177# endif 
    170178   ! 
     179#if defined key_bdy 
     180   CHARACTER(len=20), PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  cn_trc_dflt          ! Default OBC condition for all tracers 
     181   CHARACTER(len=20), PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  cn_trc               ! Choice of boundary condition for tracers 
     182   INTEGER,           PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  nn_trcdmp_bdy        !: =T Tracer damping 
     183   ! External data structure of BDY for TOP. Available elements: cn_obc, ll_trc, trcnow, dmp 
     184   TYPE(OBC_DATA),    PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET ::  trcdta_bdy           !: bdy external data (local process) 
     185#endif 
     186   ! 
    171187 
    172188   !!---------------------------------------------------------------------- 
     
    189205         &      cvol(jpi,jpj,jpk)     , rdttrc(jpk)           , trai(jptra)           ,       & 
    190206         &      ctrcnm(jptra)         , ctrcln(jptra)         , ctrcun(jptra)         ,       &  
    191          &      ln_trc_ini(jptra)     , ln_trc_wri(jptra)                             ,  STAT = trc_alloc  )   
     207         &      ln_trc_ini(jptra)     , ln_trc_wri(jptra)                             ,       & 
     208#if defined key_my_trc 
     209         &      ln_trc_sbc(jptra)     , ln_trc_cbc(jptra)     , ln_trc_obc(jptra)     ,       & 
     210#endif 
     211#if defined key_bdy 
     212         &      cn_trc_dflt(nb_bdy)   , cn_trc(nb_bdy)        , nn_trcdmp_bdy(nb_bdy) ,       & 
     213         &      trcdta_bdy(jptra,nb_bdy)                                              ,       & 
     214#endif 
     215         &      STAT = trc_alloc  ) 
    192216 
    193217      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays') 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/trcbc.F90

    r4624 r5160  
    44   !! TOP :  module for passive tracer boundary conditions 
    55   !!===================================================================== 
    6    !!---------------------------------------------------------------------- 
    7 #if  defined key_top  
     6   !! History :  3.5 !  2014-04  (M. Vichi, T. Lovato)  Original 
     7   !!            3.6 !  2015-03  (T . Lovato) Revision and BDY support 
     8   !!---------------------------------------------------------------------- 
     9#if defined key_top 
    810   !!---------------------------------------------------------------------- 
    911   !!   'key_top'                                                TOP model  
    1012   !!---------------------------------------------------------------------- 
    11    !!   trc_dta    : read and time interpolated passive tracer data 
     13   !!   trc_bc       : read and time interpolated tracer Boundary Conditions 
    1214   !!---------------------------------------------------------------------- 
    1315   USE par_trc       !  passive tracers parameters 
     
    1719   USE lib_mpp       !  MPP library 
    1820   USE fldread       !  read input fields 
     21#if defined key_bdy 
     22   USE bdy_oce, only: nb_bdy , idx_bdy, ln_coords_file, rn_time_dmp, rn_time_dmp_out 
     23#endif 
    1924 
    2025   IMPLICIT NONE 
     
    2429   PUBLIC   trc_bc_read    ! called in trcstp.F90 or within 
    2530 
    26    INTEGER  , SAVE, PUBLIC                             :: nb_trcobc   ! number of tracers with open BC 
    27    INTEGER  , SAVE, PUBLIC                             :: nb_trcsbc   ! number of tracers with surface BC 
    28    INTEGER  , SAVE, PUBLIC                             :: nb_trccbc   ! number of tracers with coastal BC 
     31   INTEGER  , SAVE, PUBLIC                             :: nb_trcobc    ! number of tracers with open BC 
     32   INTEGER  , SAVE, PUBLIC                             :: nb_trcsbc    ! number of tracers with surface BC 
     33   INTEGER  , SAVE, PUBLIC                             :: nb_trccbc    ! number of tracers with coastal BC 
    2934   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indobc ! index of tracer with OBC data 
    3035   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indsbc ! index of tracer with SBC data 
    3136   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indcbc ! index of tracer with CBC data 
    32    INTEGER  , SAVE, PUBLIC                             :: ntra_obc     ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking 
    33    INTEGER  , SAVE, PUBLIC                             :: ntra_sbc     ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking 
    34    INTEGER  , SAVE, PUBLIC                             :: ntra_cbc     ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking 
    35    REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trofac   ! multiplicative factor for OBCtracer values 
    36    TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trcobc   ! structure of data input OBC (file informations, fields read) 
    37    REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trsfac   ! multiplicative factor for SBC tracer values 
    38    TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trcsbc   ! structure of data input SBC (file informations, fields read) 
    39    REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trcfac   ! multiplicative factor for CBC tracer values 
    40    TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trccbc   ! structure of data input CBC (file informations, fields read) 
     37   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trsfac    ! multiplicative factor for SBC tracer values 
     38   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trcsbc    ! structure of data input SBC (file informations, fields read) 
     39   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trcfac    ! multiplicative factor for CBC tracer values 
     40   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trccbc    ! structure of data input CBC (file informations, fields read) 
     41   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trofac    ! multiplicative factor for OBCtracer values 
     42   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:), TARGET  :: sf_trcobc    ! structure of data input OBC (file informations, fields read) 
     43   TYPE(MAP_POINTER), ALLOCATABLE, DIMENSION(:) :: nbmap_ptr   ! array of pointers to nbmap 
    4144 
    4245   !! * Substitutions 
    4346#  include "domzgr_substitute.h90" 
    4447   !!---------------------------------------------------------------------- 
    45    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    46    !! $Id: trcdta.F90 2977 2011-10-22 13:46:41Z cetlod $  
     48   !! NEMO/OPA 3.6 , NEMO Consortium (2015) 
     49   !! $Id$ 
    4750   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4851   !!---------------------------------------------------------------------- 
     
    6063      ! 
    6164      INTEGER,INTENT(IN) :: ntrc                           ! number of tracers 
    62       INTEGER            :: jl, jn                         ! dummy loop indices 
     65      INTEGER            :: jl, jn , ib, ibd, ii, ij, ik   ! dummy loop indices 
    6366      INTEGER            :: ierr0, ierr1, ierr2, ierr3     ! temporary integers 
    64       INTEGER            ::  ios                           ! Local integer output status for namelist read 
     67      INTEGER            :: ios                            ! Local integer output status for namelist read 
     68      INTEGER            :: nblen, igrd                    ! support arrays for BDY 
    6569      CHARACTER(len=100) :: clndta, clntrc 
    6670      ! 
    67       CHARACTER(len=100) :: cn_dir 
     71      CHARACTER(len=100) :: cn_dir_sbc, cn_dir_cbc, cn_dir_obc 
     72 
    6873      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) :: slf_i  ! local array of namelist informations on the fields to read 
    6974      TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcobc    ! open 
     
    7479      REAL(wp)   , DIMENSION(jpmaxtrc) :: rn_trcfac    ! multiplicative factor for tracer values 
    7580      !! 
    76       NAMELIST/namtrc_bc/ cn_dir, sn_trcobc, rn_trofac, sn_trcsbc, rn_trsfac, sn_trccbc, rn_trcfac  
     81      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#if defined key_bdy 
     83      NAMELIST/namtrc_bdy/ cn_trc_dflt, cn_trc, nn_trcdmp_bdy 
     84#endif 
    7785      !!---------------------------------------------------------------------- 
    7886      IF( nn_timing == 1 )  CALL timing_start('trc_bc_init') 
    7987      ! 
     88      IF( lwp ) THEN 
     89         WRITE(numout,*) ' ' 
     90         WRITE(numout,*) 'trc_bc_init : Tracers Boundary Conditions (BC)' 
     91         WRITE(numout,*) '~~~~~~~~~~~ ' 
     92      ENDIF 
    8093      !  Initialisation and local array allocation 
    8194      ierr0 = 0  ;  ierr1 = 0  ;  ierr2 = 0  ;  ierr3 = 0   
     
    107120      n_trc_indcbc(:) = 0 
    108121      ! 
    109       DO jn = 1, ntrc 
    110          IF( ln_trc_obc(jn) ) THEN 
    111              nb_trcobc       = nb_trcobc + 1  
    112              n_trc_indobc(jn) = nb_trcobc  
    113          ENDIF 
    114          IF( ln_trc_sbc(jn) ) THEN 
    115              nb_trcsbc       = nb_trcsbc + 1 
    116              n_trc_indsbc(jn) = nb_trcsbc 
    117          ENDIF 
    118          IF( ln_trc_cbc(jn) ) THEN 
    119              nb_trccbc       = nb_trccbc + 1 
    120              n_trc_indcbc(jn) = nb_trccbc 
    121          ENDIF 
    122       ENDDO 
    123       ntra_obc = MAX( 1, nb_trcobc )   ! To avoid compilation error with bounds checking 
    124       IF( lwp ) WRITE(numout,*) ' ' 
    125       IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with open boundary data :', nb_trcobc 
    126       IF( lwp ) WRITE(numout,*) ' ' 
    127       ntra_sbc = MAX( 1, nb_trcsbc )   ! To avoid compilation error with bounds checking 
    128       IF( lwp ) WRITE(numout,*) ' ' 
    129       IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with surface boundary data :', nb_trcsbc 
    130       IF( lwp ) WRITE(numout,*) ' ' 
    131       ntra_cbc = MAX( 1, nb_trccbc )   ! To avoid compilation error with bounds checking 
    132       IF( lwp ) WRITE(numout,*) ' ' 
    133       IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with coastal boundary data :', nb_trccbc 
    134       IF( lwp ) WRITE(numout,*) ' ' 
    135  
     122      ! Read Boundary Conditions Namelists 
    136123      REWIND( numnat_ref )              ! Namelist namtrc_bc in reference namelist : Passive tracer data structure 
    137124      READ  ( numnat_ref, namtrc_bc, IOSTAT = ios, ERR = 901) 
     
    143130      IF(lwm) WRITE ( numont, namtrc_bc ) 
    144131 
    145       ! print some information for each  
     132#if defined key_bdy 
     133      REWIND( numnat_ref )              ! Namelist namtrc_bc in reference namelist : Passive tracer data structure 
     134      READ  ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903) 
     135903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp ) 
     136 
     137      REWIND( numnat_cfg )              ! Namelist namtrc_bc in configuration namelist : Passive tracer data structure 
     138      READ  ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 ) 
     139904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in configuration namelist', lwp ) 
     140      IF(lwm) WRITE ( numont, namtrc_bdy ) 
     141      ! setup up preliminary informations for BDY structure 
     142      DO jn = 1, ntrc 
     143         DO ib = 1, nb_bdy 
     144            ! Set type of obc in BDY data structure (around here we may plug user override of obc type from nml) 
     145            IF ( ln_trc_obc(jn) ) THEN 
     146               trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc(ib) ) 
     147            ELSE 
     148               trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc_dflt(ib) ) 
     149            ENDIF 
     150            ! set damping use in BDY data structure 
     151            trcdta_bdy(jn,ib)%dmp = .false. 
     152            IF(nn_trcdmp_bdy(ib) .EQ. 1 .AND. ln_trc_obc(jn) ) trcdta_bdy(jn,ib)%dmp = .true. 
     153            IF(nn_trcdmp_bdy(ib) .EQ. 2 ) trcdta_bdy(jn,ib)%dmp = .true. 
     154            IF(trcdta_bdy(jn,ib)%cn_obc == 'frs' .AND. nn_trcdmp_bdy(ib) .NE. 0 )  & 
     155                & CALL ctl_stop( 'Use FRS OR relaxation' ) 
     156            IF (nn_trcdmp_bdy(ib) .LT. 0 .OR. nn_trcdmp_bdy(ib) .GT. 2)            & 
     157                & CALL ctl_stop( 'Not a valid option for nn_trcdmp_bdy. Allowed: 0,1,2.' ) 
     158         ENDDO 
     159      ENDDO 
     160 
     161#else 
     162      ! Force all tracers OBC to false if bdy not used 
     163      ln_trc_obc = .false. 
     164#endif 
     165      ! compose BC data indexes 
     166      DO jn = 1, ntrc 
     167         IF( ln_trc_obc(jn) ) THEN 
     168             nb_trcobc       = nb_trcobc + 1  ; n_trc_indobc(jn) = nb_trcobc 
     169         ENDIF 
     170         IF( ln_trc_sbc(jn) ) THEN 
     171             nb_trcsbc       = nb_trcsbc + 1  ; n_trc_indsbc(jn) = nb_trcsbc 
     172         ENDIF 
     173         IF( ln_trc_cbc(jn) ) THEN 
     174             nb_trccbc       = nb_trccbc + 1  ; n_trc_indcbc(jn) = nb_trccbc 
     175         ENDIF 
     176      ENDDO 
     177 
     178      ! Print summmary of Boundary Conditions 
    146179      IF( lwp ) THEN 
     180         WRITE(numout,*) ' ' 
     181         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with SURFACE BCs data:', nb_trcsbc 
     182         IF ( nb_trcsbc > 0 ) THEN 
     183            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact. ' 
     184            DO jn = 1, ntrc 
     185               IF ( ln_trc_sbc(jn) ) WRITE(numout,9001) jn, TRIM( sn_trcsbc(jn)%clvar ), 'SBC', rn_trsfac(jn) 
     186            ENDDO 
     187         ENDIF 
     188         WRITE(numout,'(2a)') '   SURFACE BC data repository : ', TRIM(cn_dir_sbc) 
     189 
     190         WRITE(numout,*) ' ' 
     191         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with COASTAL BCs data:', nb_trccbc 
     192         IF ( nb_trccbc > 0 ) THEN 
     193            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact. ' 
     194            DO jn = 1, ntrc 
     195               IF ( ln_trc_cbc(jn) ) WRITE(numout, 9001) jn, TRIM( sn_trccbc(jn)%clvar ), 'CBC', rn_trcfac(jn) 
     196            ENDDO 
     197         ENDIF 
     198         WRITE(numout,'(2a)') '   COASTAL BC data repository : ', TRIM(cn_dir_cbc) 
     199 
     200         WRITE(numout,*) ' ' 
     201         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with OPEN BCs data:', nb_trcobc 
     202#if defined key_bdy 
     203         IF ( nb_trcobc > 0 ) THEN 
     204            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact.   OBC Settings' 
     205            DO jn = 1, ntrc 
     206               IF ( ln_trc_obc(jn) )  WRITE(numout, 9001) jn, TRIM( sn_trcobc(jn)%clvar ), 'OBC', rn_trofac(jn), (trcdta_bdy(jn,ib)%cn_obc,ib=1,nb_bdy) 
     207               IF ( .NOT. ln_trc_obc(jn) )  WRITE(numout, 9002) jn, 'Set data to IC and use default condition', (trcdta_bdy(jn,ib)%cn_obc,ib=1,nb_bdy) 
     208            ENDDO 
     209            WRITE(numout,*) ' ' 
     210            DO ib = 1, nb_bdy 
     211                IF (nn_trcdmp_bdy(ib) .EQ. 0) WRITE(numout,9003) '   Boundary ',ib,' -> NO damping of tracers' 
     212                IF (nn_trcdmp_bdy(ib) .EQ. 1) WRITE(numout,9003) '   Boundary ',ib,' -> damping ONLY for tracers with external data provided' 
     213                IF (nn_trcdmp_bdy(ib) .EQ. 2) WRITE(numout,9003) '   Boundary ',ib,' -> damping of ALL tracers' 
     214                IF (nn_trcdmp_bdy(ib) .GT. 0) THEN 
     215                   WRITE(numout,9003) '     USE damping parameters from nambdy for boundary ', ib,' : ' 
     216                   WRITE(numout,'(a,f10.2,a)') '     - Inflow damping time scale  : ',rn_time_dmp(ib),' days' 
     217                   WRITE(numout,'(a,f10.2,a)') '     - Outflow damping time scale : ',rn_time_dmp_out(ib),' days' 
     218                ENDIF 
     219            ENDDO 
     220         ENDIF 
     221#endif 
     222         WRITE(numout,'(2a)') '   OPEN BC data repository : ', TRIM(cn_dir_obc) 
     223      ENDIF 
     2249001  FORMAT(2x,i5, 3x, a15, 3x, a5, 6x, e11.3, 4x, 10a13) 
     2259002  FORMAT(2x,i5, 3x, a41, 3x, 10a13) 
     2269003  FORMAT(a, i5, a) 
     227 
     228      ! 
     229#if defined key_bdy 
     230      ! OPEN Lateral boundary conditions 
     231      IF( nb_trcobc > 0 ) THEN  
     232         ALLOCATE ( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), nbmap_ptr(nb_trcobc), STAT=ierr1 ) 
     233         IF( ierr1 > 0 ) THEN 
     234            CALL ctl_stop( 'trc_bc_init: unable to allocate sf_trcobc structure' )   ;   RETURN 
     235         ENDIF 
     236 
     237         igrd = 1                       ! Everything is at T-points here 
     238 
    147239         DO jn = 1, ntrc 
    148             IF( ln_trc_obc(jn) )  THEN     
    149                clndta = TRIM( sn_trcobc(jn)%clvar )  
    150                IF(lwp) WRITE(numout,*) 'Preparing to read OBC data file for passive tracer number :', jn, ' name : ', clndta, &  
    151                &               ' multiplicative factor : ', rn_trofac(jn) 
    152             ENDIF 
    153             IF( ln_trc_sbc(jn) )  THEN     
    154                clndta = TRIM( sn_trcsbc(jn)%clvar )  
    155                IF(lwp) WRITE(numout,*) 'Preparing to read SBC data file for passive tracer number :', jn, ' name : ', clndta, &  
    156                &               ' multiplicative factor : ', rn_trsfac(jn) 
    157             ENDIF 
    158             IF( ln_trc_cbc(jn) )  THEN     
    159                clndta = TRIM( sn_trccbc(jn)%clvar )  
    160                IF(lwp) WRITE(numout,*) 'Preparing to read CBC data file for passive tracer number :', jn, ' name : ', clndta, &  
    161                &               ' multiplicative factor : ', rn_trcfac(jn) 
    162             ENDIF 
    163          END DO 
    164       ENDIF 
    165       ! 
    166       ! The following code is written this way to reduce memory usage and repeated for each boundary data 
    167       ! MAV: note that this is just a placeholder and the dimensions must be changed according to  
    168       !      what will be done with BDY. A new structure will probably need to be included 
    169       ! 
    170       ! OPEN Lateral boundary conditions 
    171       IF( nb_trcobc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero 
    172          ALLOCATE( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), STAT=ierr1 ) 
    173          IF( ierr1 > 0 ) THEN 
    174             CALL ctl_stop( 'trc_bc_init: unable to allocate  sf_trcobc structure' )   ;   RETURN 
    175          ENDIF 
    176          ! 
    177          DO jn = 1, ntrc 
    178             IF( ln_trc_obc(jn) ) THEN      ! update passive tracers arrays with input data read from file 
    179                jl = n_trc_indobc(jn) 
    180                slf_i(jl)    = sn_trcobc(jn) 
    181                rf_trofac(jl) = rn_trofac(jn) 
    182                                             ALLOCATE( sf_trcobc(jl)%fnow(jpi,jpj,jpk)   , STAT=ierr2 ) 
    183                IF( sn_trcobc(jn)%ln_tint )  ALLOCATE( sf_trcobc(jl)%fdta(jpi,jpj,jpk,2) , STAT=ierr3 ) 
    184                IF( ierr2 + ierr3 > 0 ) THEN 
    185                  CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer OBC data arrays' )   ;   RETURN 
     240            DO ib = 1, nb_bdy 
     241 
     242               nblen = idx_bdy(ib)%nblen(igrd) 
     243 
     244               IF ( ln_trc_obc(jn) ) THEN 
     245               ! Initialise from external data 
     246                  jl = n_trc_indobc(jn) 
     247                  slf_i(jl)    = sn_trcobc(jn) 
     248                  rf_trofac(jl) = rn_trofac(jn) 
     249                                               ALLOCATE( sf_trcobc(jl)%fnow(nblen,1,jpk)   , STAT=ierr2 ) 
     250                  IF( sn_trcobc(jn)%ln_tint )  ALLOCATE( sf_trcobc(jl)%fdta(nblen,1,jpk,2) , STAT=ierr3 ) 
     251                  IF( ierr2 + ierr3 > 0 ) THEN 
     252                    CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer OBC data arrays' )   ;   RETURN 
     253                  ENDIF 
     254                  trcdta_bdy(jn,ib)%trc => sf_trcobc(jl)%fnow(:,1,:) 
     255                  trcdta_bdy(jn,ib)%rn_fac = rf_trofac(jl) 
     256                  ! create OBC mapping array 
     257                  nbmap_ptr(jl)%ptr => idx_bdy(ib)%nbmap(:,igrd) 
     258                  nbmap_ptr(jl)%ll_unstruc = ln_coords_file(igrd) 
     259               ELSE 
     260               ! Initialise obc arrays from initial conditions 
     261                  ALLOCATE ( trcdta_bdy(jn,ib)%trc(nblen,jpk) ) 
     262                  DO ibd = 1, nblen 
     263                     DO ik = 1, jpkm1 
     264                        ii = idx_bdy(ib)%nbi(ibd,igrd) 
     265                        ij = idx_bdy(ib)%nbj(ibd,igrd) 
     266                        trcdta_bdy(jn,ib)%trc(ibd,ik) = trn(ii,ij,ik,jn) * tmask(ii,ij,ik) 
     267                     END DO 
     268                  END DO 
     269                  trcdta_bdy(jn,ib)%rn_fac = 1._wp 
    186270               ENDIF 
    187             ENDIF 
    188             !    
     271            ENDDO 
    189272         ENDDO 
    190          !                         ! fill sf_trcdta with slf_i and control print 
    191          CALL fld_fill( sf_trcobc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' ) 
    192          ! 
    193       ENDIF 
    194       ! 
     273 
     274         CALL fld_fill( sf_trcobc, slf_i, cn_dir_obc, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' ) 
     275      ENDIF 
     276#endif 
    195277      ! SURFACE Boundary conditions 
    196278      IF( nb_trcsbc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero 
     
    214296         ENDDO 
    215297         !                         ! fill sf_trcsbc with slf_i and control print 
    216          CALL fld_fill( sf_trcsbc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer SBC data', 'namtrc_bc' ) 
     298         CALL fld_fill( sf_trcsbc, slf_i, cn_dir_sbc, 'trc_bc_init', 'Passive tracer SBC data', 'namtrc_bc' ) 
    217299         ! 
    218300      ENDIF 
     
    239321         ENDDO 
    240322         !                         ! fill sf_trccbc with slf_i and control print 
    241          CALL fld_fill( sf_trccbc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer CBC data', 'namtrc_bc' ) 
     323         CALL fld_fill( sf_trccbc, slf_i, cn_dir_cbc, 'trc_bc_init', 'Passive tracer CBC data', 'namtrc_bc' ) 
    242324         ! 
    243325      ENDIF 
     
    249331 
    250332 
    251    SUBROUTINE trc_bc_read(kt) 
     333   SUBROUTINE trc_bc_read(kt, jit) 
    252334      !!---------------------------------------------------------------------- 
    253335      !!                   ***  ROUTINE trc_bc_init  *** 
     
    264346      !! * Arguments 
    265347      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    266  
     348      INTEGER, INTENT( in ), OPTIONAL ::   jit   ! subcycle time-step index (for timesplitting option) 
    267349      !!--------------------------------------------------------------------- 
    268350      ! 
    269351      IF( nn_timing == 1 )  CALL timing_start('trc_bc_read') 
    270352 
    271       IF( kt == nit000 ) THEN 
    272          IF(lwp) WRITE(numout,*) 
    273          IF(lwp) WRITE(numout,*) 'trc_bc_read : Surface boundary conditions for passive tracers.' 
    274          IF(lwp) WRITE(numout,*) '~~~~~~~ ' 
    275       ENDIF 
    276  
    277       ! OPEN boundary conditions: DOES NOT WORK. Waiting for stable BDY 
    278       IF( nb_trcobc > 0 ) THEN 
    279         if (lwp) write(numout,'(a,i5,a,i5)') '   reading OBC data for ', nb_trcobc ,' variables at step ', kt 
    280         CALL fld_read(kt,1,sf_trcobc) 
    281         ! vertical interpolation on s-grid and partial step to be added 
    282       ENDIF 
    283  
    284       ! SURFACE boundary conditions        
    285       IF( nb_trcsbc > 0 ) THEN 
    286         if (lwp) write(numout,'(a,i5,a,i5)') '   reading SBC data for ', nb_trcsbc ,' variables at step ', kt 
    287         CALL fld_read(kt,1,sf_trcsbc) 
    288       ENDIF 
    289  
    290       ! COASTAL boundary conditions        
    291       IF( nb_trccbc > 0 ) THEN 
    292         if (lwp) write(numout,'(a,i5,a,i5)') '   reading CBC data for ', nb_trccbc ,' variables at step ', kt 
    293         CALL fld_read(kt,1,sf_trccbc) 
    294       ENDIF    
     353      IF( kt == nit000 .AND. lwp) THEN 
     354         WRITE(numout,*) 
     355         WRITE(numout,*) 'trc_bc_read : Surface boundary conditions for passive tracers.' 
     356         WRITE(numout,*) '~~~~~~~~~~~ ' 
     357      ENDIF 
     358 
     359      IF ( PRESENT(jit) ) THEN  
     360 
     361         ! OPEN boundary conditions (use time_offset=+1 as they are applied at the end of the step) 
     362         IF( nb_trcobc > 0 ) THEN 
     363           if (lwp) write(numout,'(a,i5,a,i10)') '   reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 
     364           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcobc, map=nbmap_ptr, kit=jit, kt_offset=+1) 
     365         ENDIF 
     366 
     367         ! SURFACE boundary conditions 
     368         IF( nb_trcsbc > 0 ) THEN 
     369           if (lwp) write(numout,'(a,i5,a,i10)') '   reading SBC data for ', nb_trcsbc ,' variable(s) at step ', kt 
     370           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcsbc, kit=jit) 
     371         ENDIF 
     372 
     373         ! COASTAL boundary conditions 
     374         IF( nb_trccbc > 0 ) THEN 
     375           if (lwp) write(numout,'(a,i5,a,i10)') '   reading CBC data for ', nb_trccbc ,' variable(s) at step ', kt 
     376           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trccbc, kit=jit) 
     377         ENDIF 
     378 
     379      ELSE 
     380 
     381         ! OPEN boundary conditions (use time_offset=+1 as they are applied at the end of the step) 
     382         IF( nb_trcobc > 0 ) THEN 
     383           if (lwp) write(numout,'(a,i5,a,i10)') '   reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 
     384           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcobc, map=nbmap_ptr, kt_offset=+1) 
     385         ENDIF 
     386 
     387         ! SURFACE boundary conditions 
     388         IF( nb_trcsbc > 0 ) THEN 
     389           if (lwp) write(numout,'(a,i5,a,i10)') '   reading SBC data for ', nb_trcsbc ,' variable(s) at step ', kt 
     390           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcsbc) 
     391         ENDIF 
     392 
     393         ! COASTAL boundary conditions 
     394         IF( nb_trccbc > 0 ) THEN 
     395           if (lwp) write(numout,'(a,i5,a,i10)') '   reading CBC data for ', nb_trccbc ,' variable(s) at step ', kt 
     396           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trccbc) 
     397         ENDIF 
     398 
     399      ENDIF 
     400 
    295401      ! 
    296402      IF( nn_timing == 1 )  CALL timing_stop('trc_bc_read') 
     
    303409   !!---------------------------------------------------------------------- 
    304410CONTAINS 
     411 
     412   SUBROUTINE trc_bc_init( ntrc )        ! Empty routine 
     413      INTEGER,INTENT(IN) :: ntrc                           ! number of tracers 
     414      WRITE(*,*) 'trc_bc_init: You should not have seen this print! error?', kt 
     415   END SUBROUTINE trc_bc_init 
     416 
    305417   SUBROUTINE trc_bc_read( kt )        ! Empty routine 
    306418      WRITE(*,*) 'trc_bc_read: You should not have seen this print! error?', kt 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/trcdta.F90

    r4624 r5160  
    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    !!---------------------------------------------------------------------- 
    12 #if  defined key_top  
     11   !!            3.6   !  2015-03  (T. Lovato) revision of code log info 
     12   !!---------------------------------------------------------------------- 
     13#if defined key_top  
    1314   !!---------------------------------------------------------------------- 
    1415   !!   'key_top'                                                TOP model  
     
    7273      IF( nn_timing == 1 )  CALL timing_start('trc_dta_init') 
    7374      ! 
     75      IF( lwp ) THEN 
     76         WRITE(numout,*) ' ' 
     77         WRITE(numout,*) '  trc_dta_init : Tracers Initial Conditions (IC)' 
     78         WRITE(numout,*) '  ~~~~~~~~~~~ ' 
     79      ENDIF 
     80      ! 
    7481      !  Initialisation 
    7582      ierr0 = 0  ;  ierr1 = 0  ;  ierr2 = 0  ;  ierr3 = 0   
     
    7784      ALLOCATE( n_trc_index(ntrc), slf_i(ntrc), STAT=ierr0 ) 
    7885      IF( ierr0 > 0 ) THEN 
    79          CALL ctl_stop( 'trc_nam: unable to allocate n_trc_index' )   ;   RETURN 
     86         CALL ctl_stop( 'trc_dta_init: unable to allocate n_trc_index' )   ;   RETURN 
    8087      ENDIF 
    8188      nb_trcdta      = 0 
     
    97104      REWIND( numnat_ref )              ! Namelist namtrc_dta in reference namelist : Passive tracer input data 
    98105      READ  ( numnat_ref, namtrc_dta, IOSTAT = ios, ERR = 901) 
    99 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta in reference namelist', lwp ) 
     106901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta_init in reference namelist', lwp ) 
    100107 
    101108      REWIND( numnat_cfg )              ! Namelist namtrc_dta in configuration namelist : Passive tracer input data 
    102109      READ  ( numnat_cfg, namtrc_dta, IOSTAT = ios, ERR = 902 ) 
    103 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta in configuration namelist', lwp ) 
     110902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dta_init in configuration namelist', lwp ) 
    104111      IF(lwm) WRITE ( numont, namtrc_dta ) 
    105112 
     
    109116               clndta = TRIM( sn_trcdta(jn)%clvar )  
    110117               clntrc = TRIM( ctrcnm   (jn)       )  
     118               if (jn > jptra) clntrc='Dummy' ! By pass weird formats in ocean.output if ntrc > jptra 
    111119               zfact  = rn_trfac(jn) 
    112120               IF( clndta /=  clntrc ) THEN  
    113                   CALL ctl_warn( 'trc_dta_init: passive tracer data initialisation :  ',   & 
    114                   &              'the variable name in the data file : '//clndta//   &  
    115                   &              '  must be the same than the name of the passive tracer : '//clntrc//' ') 
     121                  CALL ctl_warn( 'trc_dta_init: passive tracer data initialisation    ',   & 
     122                  &              'Input name of data file : '//TRIM(clndta)//   & 
     123                  &              ' differs from that of tracer : '//TRIM(clntrc)//' ') 
    116124               ENDIF 
    117                WRITE(numout,*) ' read an initial file for passive tracer number :', jn, ' name : ', clndta, &  
    118                &               ' multiplicative factor : ', zfact 
     125               WRITE(numout,*) ' ' 
     126               WRITE(numout,'(a, i3,3a,e11.3)') ' Read IC file for tracer number :', & 
     127               &            jn, ', name : ', TRIM(clndta), ', Multiplicative Scaling factor : ', zfact 
    119128            ENDIF 
    120129         END DO 
     
    124133         ALLOCATE( sf_trcdta(nb_trcdta), rf_trfac(nb_trcdta), STAT=ierr1 ) 
    125134         IF( ierr1 > 0 ) THEN 
    126             CALL ctl_stop( 'trc_dta_ini: unable to allocate  sf_trcdta structure' )   ;   RETURN 
     135            CALL ctl_stop( 'trc_dta_init: unable to allocate  sf_trcdta structure' )   ;   RETURN 
    127136         ENDIF 
    128137         ! 
     
    135144               IF( sn_trcdta(jn)%ln_tint )  ALLOCATE( sf_trcdta(jl)%fdta(jpi,jpj,jpk,2) , STAT=ierr3 ) 
    136145               IF( ierr2 + ierr3 > 0 ) THEN 
    137                  CALL ctl_stop( 'trc_dta : unable to allocate passive tracer data arrays' )   ;   RETURN 
     146                 CALL ctl_stop( 'trc_dta_init : unable to allocate passive tracer data arrays' )   ;   RETURN 
    138147               ENDIF 
    139148            ENDIF 
     
    141150         ENDDO 
    142151         !                         ! fill sf_trcdta with slf_i and control print 
    143          CALL fld_fill( sf_trcdta, slf_i, cn_dir, 'trc_dta', 'Passive tracer data', 'namtrc' ) 
     152         CALL fld_fill( sf_trcdta, slf_i, cn_dir, 'trc_dta_init', 'Passive tracer data', 'namtrc' ) 
    144153         ! 
    145154      ENDIF 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r5120 r5160  
    3131   USE lib_mpp         ! distribued memory computing library 
    3232   USE sbc_oce 
     33   USE trcbc,   only : trc_bc_init ! generalized Boundary Conditions 
    3334  
    3435   IMPLICIT NONE 
     
    107108      ENDIF 
    108109 
     110      ! Initialisation of tracers Initial Conditions 
    109111      IF( ln_trcdta )      CALL trc_dta_init(jptra) 
    110112 
     113      ! Initialisation of tracers Boundary Conditions 
     114      IF( lk_my_trc )     CALL trc_bc_init(jptra) 
    111115 
    112116      IF( ln_rsttr ) THEN 
  • branches/2015/dev_r5144_CMCC5_BDY_for_TOP/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r4990 r5160  
    182182 
    183183 
    184       IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
     184      IF(lwp) WRITE(numout,*) 'trc_nam_run : read the passive tracer namelists' 
    185185      IF(lwp) WRITE(numout,*) '~~~~~~~' 
    186186 
     
    225225      TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput 
    226226      !! 
    227       NAMELIST/namtrc/ sn_tracer, ln_trcdta,ln_trcdmp, ln_trcdmp_clo 
     227      NAMELIST/namtrc/ sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo 
    228228   
    229229      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     
    231231      !!--------------------------------------------------------------------- 
    232232      IF(lwp) WRITE(numout,*) 
    233       IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
     233      IF(lwp) WRITE(numout,*) 'trc_nam_trc : read the passive tracer namelists' 
    234234      IF(lwp) WRITE(numout,*) '~~~~~~~' 
    235235 
     
    249249         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  ) 
    250250         ln_trc_ini(jn) =       sn_tracer(jn)%llinit 
     251#if defined key_my_trc 
     252         ln_trc_sbc(jn) =       sn_tracer(jn)%llsbc 
     253         ln_trc_cbc(jn) =       sn_tracer(jn)%llcbc 
     254         ln_trc_obc(jn) =       sn_tracer(jn)%llobc 
     255#endif 
    251256         ln_trc_wri(jn) =       sn_tracer(jn)%llsave 
    252257      END DO 
    253        
     258 
    254259    END SUBROUTINE trc_nam_trc 
    255260 
     
    275280      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    276281      !!--------------------------------------------------------------------- 
    277  
    278       IF(lwp) WRITE(numout,*)  
    279       IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options' 
    280       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    281282 
    282283      IF(lwp) WRITE(numout,*) 
Note: See TracChangeset for help on using the changeset viewer.