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 7835 for branches/UKMO/CO6_shelfclimate_fabm/NEMOGCM/NEMO/TOP_SRC/trcbc.F90 – NEMO

Ignore:
Timestamp:
2017-03-24T16:06:42+01:00 (7 years ago)
Author:
dford
Message:

Initial attempt to add FABM. In theory this should give equivalent results to PML gitlab commit 2e51db55.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/CO6_shelfclimate_fabm/NEMOGCM/NEMO/TOP_SRC/trcbc.F90

    r7567 r7835  
    77   !!            3.6 !  2015-03  (T . Lovato) Revision and BDY support 
    88   !!---------------------------------------------------------------------- 
    9 #if  defined key_top  
     9#if defined key_top 
    1010   !!---------------------------------------------------------------------- 
    1111   !!   'key_top'                                                TOP model  
     
    2929   PUBLIC   trc_bc_read    ! called in trcstp.F90 or within 
    3030 
    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 
     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 
    3434   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indobc ! index of tracer with OBC data 
    3535   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indsbc ! index of tracer with SBC data 
    3636   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indcbc ! index of tracer with CBC data 
    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) 
    4141   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:,:)  :: rf_trofac    ! multiplicative factor for OBCtracer values 
    4242   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET  :: sf_trcobc    ! structure of data input OBC (file informations, fields read) 
     
    6565      INTEGER            :: jl, jn , ib, ibd, ii, ij, ik   ! dummy loop indices 
    6666      INTEGER            :: ierr0, ierr1, ierr2, ierr3     ! temporary integers 
    67       INTEGER            ::  ios                           ! Local integer output status for namelist read 
     67      INTEGER            :: ios                            ! Local integer output status for namelist read 
    6868      INTEGER            :: nblen, igrd                    ! support arrays for BDY 
    6969      CHARACTER(len=100) :: clndta, clntrc 
     
    130130      DO ib = 1, nb_bdy 
    131131#endif 
    132       READ  ( numnat_cfg, namtrc_bc, IOSTAT = ios, ERR = 902 ) 
    133 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bc in configuration namelist', lwp ) 
    134       IF(lwm) WRITE ( numont, namtrc_bc ) 
     132        READ  ( numnat_cfg, namtrc_bc, IOSTAT = ios, ERR = 902 ) 
     133902     IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bc in configuration namelist', lwp ) 
     134        IF(lwm) WRITE ( numont, namtrc_bc ) 
    135135#if defined key_bdy 
    136136        sn_trcobc(:,ib)=sn_trcobc2(:) 
     
    190190         IF ( nb_trcsbc > 0 ) THEN 
    191191            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact. ' 
    192          DO jn = 1, ntrc 
     192            DO jn = 1, ntrc 
    193193               IF ( ln_trc_sbc(jn) ) WRITE(numout,9001) jn, TRIM( sn_trcsbc(jn)%clvar ), 'SBC', rn_trsfac(jn) 
    194194            ENDDO 
    195             ENDIF 
     195         ENDIF 
    196196         WRITE(numout,'(2a)') '   SURFACE BC data repository : ', TRIM(cn_dir_sbc) 
    197197 
     
    203203               IF ( ln_trc_cbc(jn) ) WRITE(numout, 9001) jn, TRIM( sn_trccbc(jn)%clvar ), 'CBC', rn_trcfac(jn) 
    204204            ENDDO 
    205             ENDIF 
     205         ENDIF 
    206206         WRITE(numout,'(2a)') '   COASTAL BC data repository : ', TRIM(cn_dir_cbc) 
    207207 
     
    227227                   WRITE(numout,'(a,f10.2,a)') '     - Inflow damping time scale  : ',rn_time_dmp(ib),' days' 
    228228                   WRITE(numout,'(a,f10.2,a)') '     - Outflow damping time scale : ',rn_time_dmp_out(ib),' days' 
    229             ENDIF 
    230          END DO 
    231       ENDIF 
     229                ENDIF 
     230            ENDDO 
     231         ENDIF 
    232232#endif 
    233233         WRITE(numout,'(2a)') '   OPEN BC data repository : ', TRIM(cn_dir_obc) 
     
    243243         ALLOCATE ( sf_trcobc(nb_trcobc,nb_bdy), rf_trofac(nb_trcobc,nb_bdy), nbmap_ptr(nb_trcobc,nb_bdy), STAT=ierr1 ) 
    244244         IF( ierr1 > 0 ) THEN 
    245             CALL ctl_stop( 'trc_bc_init: unable to allocate  sf_trcobc structure' )   ;   RETURN 
     245            CALL ctl_stop( 'trc_bc_init: unable to allocate sf_trcobc structure' )   ;   RETURN 
    246246         ENDIF 
    247247 
     
    249249 
    250250         DO ib = 1, nb_bdy 
    251          DO jn = 1, ntrc 
     251            DO jn = 1, ntrc 
    252252 
    253253               nblen = idx_bdy(ib)%nblen(igrd) 
     
    255255               IF ( ln_trc_obc(jn) ) THEN 
    256256               ! Initialise from external data 
    257                jl = n_trc_indobc(jn) 
     257                  jl = n_trc_indobc(jn) 
    258258                  slf_i(jl)    = sn_trcobc(jn,ib) 
    259259                  rf_trofac(jl,ib) = rn_trofac(jn) 
    260260                                               ALLOCATE( sf_trcobc(jl,ib)%fnow(nblen,1,jpk)   , STAT=ierr2 ) 
    261261                  IF( sn_trcobc(jn,ib)%ln_tint )  ALLOCATE( sf_trcobc(jl,ib)%fdta(nblen,1,jpk,2) , STAT=ierr3 ) 
    262                IF( ierr2 + ierr3 > 0 ) THEN 
    263                  CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer OBC data arrays' )   ;   RETURN 
    264                ENDIF 
     262                  IF( ierr2 + ierr3 > 0 ) THEN 
     263                    CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer OBC data arrays' )   ;   RETURN 
     264                  ENDIF 
    265265                  trcdta_bdy(jn,ib)%trc => sf_trcobc(jl,ib)%fnow(:,1,:) 
    266266                  trcdta_bdy(jn,ib)%rn_fac = rf_trofac(jl,ib) 
     
    279279                  END DO 
    280280                  trcdta_bdy(jn,ib)%rn_fac = 1._wp 
    281             ENDIF 
    282          ENDDO 
     281               ENDIF 
     282            ENDDO 
    283283            CALL fld_fill( sf_trcobc(:,ib), slf_i, cn_dir_obc, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' ) 
    284284         ENDDO 
     
    371371      IF ( PRESENT(jit) ) THEN  
    372372 
     373#ifdef key_bdy 
    373374         ! OPEN boundary conditions (use time_offset=+1 as they are applied at the end of the step) 
    374       IF( nb_trcobc > 0 ) THEN 
     375         IF( nb_trcobc > 0 ) THEN 
    375376           if (lwp) write(numout,'(a,i5,a,i10)') '   reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 
    376377           DO ib = 1,nb_bdy 
    377378             CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcobc(:,ib), map=nbmap_ptr(:,ib), kit=jit, kt_offset=+1) 
    378379           ENDDO 
    379       ENDIF 
    380  
    381       ! SURFACE boundary conditions        
    382       IF( nb_trcsbc > 0 ) THEN 
     380         ENDIF 
     381#endif 
     382 
     383         ! SURFACE boundary conditions 
     384         IF( nb_trcsbc > 0 ) THEN 
    383385           if (lwp) write(numout,'(a,i5,a,i10)') '   reading SBC data for ', nb_trcsbc ,' variable(s) at step ', kt 
    384386           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcsbc, kit=jit) 
    385       ENDIF 
    386  
    387       ! COASTAL boundary conditions        
    388       IF( nb_trccbc > 0 ) THEN 
     387         ENDIF 
     388 
     389         ! COASTAL boundary conditions 
     390         IF( nb_trccbc > 0 ) THEN 
    389391           if (lwp) write(numout,'(a,i5,a,i10)') '   reading CBC data for ', nb_trccbc ,' variable(s) at step ', kt 
    390392           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trccbc, kit=jit) 
    391       ENDIF    
     393         ENDIF 
    392394 
    393395      ELSE 
    394396 
     397#ifdef key_bdy 
    395398         ! OPEN boundary conditions (use time_offset=+1 as they are applied at the end of the step) 
    396399         IF( nb_trcobc > 0 ) THEN 
     
    400403           ENDDO 
    401404         ENDIF 
     405#endif 
    402406 
    403407         ! SURFACE boundary conditions 
Note: See TracChangeset for help on using the changeset viewer.