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 7412 for branches/2016/dev_merge_2016/NEMOGCM/NEMO/TOP_SRC/trcbc.F90 – NEMO

Ignore:
Timestamp:
2016-12-01T11:30:29+01:00 (8 years ago)
Author:
lovato
Message:

Merge dev_NOC_CMCC_merge_2016 into branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_merge_2016/NEMOGCM/NEMO/TOP_SRC/trcbc.F90

    r7403 r7412  
    2020   USE lib_mpp       !  MPP library 
    2121   USE fldread       !  read input fields 
    22 #if defined key_bdy 
    23    USE bdy_oce, only: nb_bdy , idx_bdy, ln_coords_file, rn_time_dmp, rn_time_dmp_out 
    24 #endif 
     22   USE bdy_oce,  ONLY: ln_bdy, nb_bdy , idx_bdy, ln_coords_file, rn_time_dmp, rn_time_dmp_out 
    2523 
    2624   IMPLICIT NONE 
     
    8280      NAMELIST/namtrc_bc/ cn_dir_obc, sn_trcobc, rn_trofac, cn_dir_sbc, sn_trcsbc, rn_trsfac, &  
    8381                        & cn_dir_cbc, sn_trccbc, rn_trcfac, ln_rnf_ctl, rn_bc_time 
    84 #if defined key_bdy 
    8582      NAMELIST/namtrc_bdy/ cn_trc_dflt, cn_trc, nn_trcdmp_bdy 
    86 #endif 
     83 
    8784      !!---------------------------------------------------------------------- 
    8885      IF( nn_timing == 1 )  CALL timing_start('trc_bc_ini') 
     
    132129      IF(lwm) WRITE ( numont, namtrc_bc ) 
    133130 
    134 #if defined key_bdy 
    135       REWIND( numnat_ref )              ! Namelist namtrc_bc in reference namelist : Passive tracer data structure 
    136       READ  ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903) 
    137 903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp ) 
    138  
    139       REWIND( numnat_cfg )              ! Namelist namtrc_bc in configuration namelist : Passive tracer data structure 
    140       READ  ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 ) 
    141 904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in configuration namelist', lwp ) 
    142       IF(lwm) WRITE ( numont, namtrc_bdy ) 
    143       ! setup up preliminary informations for BDY structure 
    144       DO jn = 1, ntrc 
    145          DO ib = 1, nb_bdy 
    146             ! Set type of obc in BDY data structure (TL: around here we may plug user override of obc type from nml) 
    147             IF ( ln_trc_obc(jn) ) THEN 
    148                trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc(ib) ) 
    149             ELSE 
    150                trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc_dflt(ib) ) 
    151             ENDIF 
    152             ! set damping use in BDY data structure 
    153             trcdta_bdy(jn,ib)%dmp = .false. 
    154             IF(nn_trcdmp_bdy(ib) .EQ. 1 .AND. ln_trc_obc(jn) ) trcdta_bdy(jn,ib)%dmp = .true. 
    155             IF(nn_trcdmp_bdy(ib) .EQ. 2 ) trcdta_bdy(jn,ib)%dmp = .true. 
    156             IF(trcdta_bdy(jn,ib)%cn_obc == 'frs' .AND. nn_trcdmp_bdy(ib) .NE. 0 )  & 
    157                 & CALL ctl_stop( 'Use FRS OR relaxation' ) 
    158             IF (nn_trcdmp_bdy(ib) .LT. 0 .OR. nn_trcdmp_bdy(ib) .GT. 2)            & 
    159                 & CALL ctl_stop( 'Not a valid option for nn_trcdmp_bdy. Allowed: 0,1,2.' ) 
     131      IF ( ln_bdy ) THEN 
     132         REWIND( numnat_ref )              ! Namelist namtrc_bdy in reference namelist : Passive tracer data structure 
     133         READ  ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903) 
     134903      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp ) 
     135 
     136         REWIND( numnat_cfg )              ! Namelist namtrc_bdy in configuration namelist : Passive tracer data structure 
     137         READ  ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 ) 
     138904      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in configuration namelist', lwp ) 
     139         IF(lwm) WRITE ( numont, namtrc_bdy ) 
     140       
     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 
    160159         ENDDO 
    161       ENDDO 
    162  
    163 #else 
    164       ! Force all tracers OBC to false if bdy not used 
    165       ln_trc_obc = .false. 
    166 #endif 
     160      ELSE 
     161         ! Force all tracers OBC to false if bdy not used 
     162         ln_trc_obc = .false. 
     163      ENDIF 
     164 
    167165      ! compose BC data indexes 
    168166      DO jn = 1, ntrc 
     
    203201         WRITE(numout,*) ' ' 
    204202         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with OPEN BCs data:', nb_trcobc 
    205 #if defined key_bdy 
    206          IF ( nb_trcobc > 0 ) THEN 
     203 
     204         IF ( ln_bdy .AND. nb_trcobc > 0 ) THEN 
    207205            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact.   OBC Settings' 
    208206            DO jn = 1, ntrc 
     
    222220            ENDDO 
    223221         ENDIF 
    224 #endif 
     222 
    225223         WRITE(numout,'(2a)') '   OPEN BC data repository : ', TRIM(cn_dir_obc) 
    226224      ENDIF 
     
    230228 
    231229      ! 
    232 #if defined key_bdy 
    233230      ! OPEN Lateral boundary conditions 
    234       IF( nb_trcobc > 0 ) THEN  
     231      IF( ln_bdy .AND. nb_trcobc > 0 ) THEN  
    235232         ALLOCATE ( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), nbmap_ptr(nb_trcobc), STAT=ierr1 ) 
    236233         IF( ierr1 > 0 ) THEN 
     
    277274         CALL fld_fill( sf_trcobc, slf_i, cn_dir_obc, 'trc_bc_ini', 'Passive tracer OBC data', 'namtrc_bc' ) 
    278275      ENDIF 
    279 #endif 
     276 
    280277      ! SURFACE Boundary conditions 
    281278      IF( nb_trcsbc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero 
Note: See TracChangeset for help on using the changeset viewer.