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

Ignore:
Timestamp:
2016-08-12T15:16:24+02:00 (8 years ago)
Author:
lovato
Message:

#1729 - trunk: removed key_bdy from the code and set usage of ln_bdy. Tested with SETTE.

File:
1 edited

Legend:

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

    r6140 r6862  
    1919   USE lib_mpp       !  MPP library 
    2020   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 
     21   USE bdy_oce,  ONLY: ln_bdy, nb_bdy , idx_bdy, ln_coords_file, rn_time_dmp, rn_time_dmp_out 
    2422 
    2523   IMPLICIT NONE 
     
    7876      !! 
    7977      NAMELIST/namtrc_bc/ cn_dir_sbc, cn_dir_cbc, cn_dir_obc, sn_trcobc, rn_trofac, sn_trcsbc, rn_trsfac, sn_trccbc, rn_trcfac 
    80 #if defined key_bdy 
    8178      NAMELIST/namtrc_bdy/ cn_trc_dflt, cn_trc, nn_trcdmp_bdy 
    82 #endif 
     79 
    8380      !!---------------------------------------------------------------------- 
    8481      IF( nn_timing == 1 )  CALL timing_start('trc_bc_init') 
     
    128125      IF(lwm) WRITE ( numont, namtrc_bc ) 
    129126 
    130 #if defined key_bdy 
    131       REWIND( numnat_ref )              ! Namelist namtrc_bc in reference namelist : Passive tracer data structure 
    132       READ  ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903) 
    133 903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp ) 
    134  
    135       REWIND( numnat_cfg )              ! Namelist namtrc_bc in configuration namelist : Passive tracer data structure 
    136       READ  ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 ) 
    137 904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in configuration namelist', lwp ) 
    138       IF(lwm) WRITE ( numont, namtrc_bdy ) 
    139       ! setup up preliminary informations for BDY structure 
    140       DO jn = 1, ntrc 
    141          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) 
    143             IF ( ln_trc_obc(jn) ) THEN 
    144                trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc(ib) ) 
    145             ELSE 
    146                trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc_dflt(ib) ) 
    147             ENDIF 
    148             ! set damping use in BDY data structure 
    149             trcdta_bdy(jn,ib)%dmp = .false. 
    150             IF(nn_trcdmp_bdy(ib) .EQ. 1 .AND. ln_trc_obc(jn) ) trcdta_bdy(jn,ib)%dmp = .true. 
    151             IF(nn_trcdmp_bdy(ib) .EQ. 2 ) trcdta_bdy(jn,ib)%dmp = .true. 
    152             IF(trcdta_bdy(jn,ib)%cn_obc == 'frs' .AND. nn_trcdmp_bdy(ib) .NE. 0 )  & 
    153                 & CALL ctl_stop( 'Use FRS OR relaxation' ) 
    154             IF (nn_trcdmp_bdy(ib) .LT. 0 .OR. nn_trcdmp_bdy(ib) .GT. 2)            & 
    155                 & CALL ctl_stop( 'Not a valid option for nn_trcdmp_bdy. Allowed: 0,1,2.' ) 
     127      IF ( ln_bdy ) THEN 
     128         REWIND( numnat_ref )              ! Namelist namtrc_bdy in reference namelist : Passive tracer data structure 
     129         READ  ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903) 
     130903      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp ) 
     131 
     132         REWIND( numnat_cfg )              ! Namelist namtrc_bdy in configuration namelist : Passive tracer data structure 
     133         READ  ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 ) 
     134904      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in configuration namelist', lwp ) 
     135         IF(lwm) WRITE ( numont, namtrc_bdy ) 
     136       
     137         ! setup up preliminary informations for BDY structure 
     138         DO jn = 1, ntrc 
     139            DO ib = 1, nb_bdy 
     140               ! Set type of obc in BDY data structure (around here we may plug user override of obc type from nml) 
     141               IF ( ln_trc_obc(jn) ) THEN 
     142                  trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc(ib) ) 
     143               ELSE 
     144                  trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc_dflt(ib) ) 
     145               ENDIF 
     146               ! set damping use in BDY data structure 
     147               trcdta_bdy(jn,ib)%dmp = .false. 
     148               IF(nn_trcdmp_bdy(ib) .EQ. 1 .AND. ln_trc_obc(jn) ) trcdta_bdy(jn,ib)%dmp = .true. 
     149               IF(nn_trcdmp_bdy(ib) .EQ. 2 ) trcdta_bdy(jn,ib)%dmp = .true. 
     150               IF(trcdta_bdy(jn,ib)%cn_obc == 'frs' .AND. nn_trcdmp_bdy(ib) .NE. 0 )  & 
     151                   & CALL ctl_stop( 'Use FRS OR relaxation' ) 
     152               IF (nn_trcdmp_bdy(ib) .LT. 0 .OR. nn_trcdmp_bdy(ib) .GT. 2)            & 
     153                   & CALL ctl_stop( 'Not a valid option for nn_trcdmp_bdy. Allowed: 0,1,2.' ) 
     154            ENDDO 
    156155         ENDDO 
    157       ENDDO 
    158  
    159 #else 
    160       ! Force all tracers OBC to false if bdy not used 
    161       ln_trc_obc = .false. 
    162 #endif 
     156      ELSE 
     157         ! Force all tracers OBC to false if bdy not used 
     158         ln_trc_obc = .false. 
     159      ENDIF 
     160 
    163161      ! compose BC data indexes 
    164162      DO jn = 1, ntrc 
     
    198196         WRITE(numout,*) ' ' 
    199197         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with OPEN BCs data:', nb_trcobc 
    200 #if defined key_bdy 
    201          IF ( nb_trcobc > 0 ) THEN 
     198 
     199         IF ( ln_bdy .AND. nb_trcobc > 0 ) THEN 
    202200            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact.   OBC Settings' 
    203201            DO jn = 1, ntrc 
     
    217215            ENDDO 
    218216         ENDIF 
    219 #endif 
     217 
    220218         WRITE(numout,'(2a)') '   OPEN BC data repository : ', TRIM(cn_dir_obc) 
    221219      ENDIF 
     
    225223 
    226224      ! 
    227 #if defined key_bdy 
    228225      ! OPEN Lateral boundary conditions 
    229       IF( nb_trcobc > 0 ) THEN  
     226      IF( ln_bdy .AND. nb_trcobc > 0 ) THEN  
    230227         ALLOCATE ( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), nbmap_ptr(nb_trcobc), STAT=ierr1 ) 
    231228         IF( ierr1 > 0 ) THEN 
     
    272269         CALL fld_fill( sf_trcobc, slf_i, cn_dir_obc, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' ) 
    273270      ENDIF 
    274 #endif 
     271 
    275272      ! SURFACE Boundary conditions 
    276273      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.