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.
2011WP/2011Stream2/OpenBoundaries (diff) – NEMO

Changes between Version 5 and Version 6 of 2011WP/2011Stream2/OpenBoundaries


Ignore:
Timestamp:
2011-03-11T17:46:09+01:00 (13 years ago)
Author:
davestorkey
Comment:

--

Legend:

Unmodified
Added
Removed
Modified
  • 2011WP/2011Stream2/OpenBoundaries

    v5 v6  
    161161   INTEGER, OPTIONAL  :: jit       ! barotropic subloop index 
    162162    
    163    TYPE(FLD_N), ALLOCATABLE, DIMENSION(:,:) ::   blf_i 
    164     
    165    ALLOCATE( bf   (nb_stream, nb_dta_max), STAT=ierror ) 
    166    ALLOCATE( blf_i(nb_stream, nb_dta_max), STAT=ierror ) 
    167  
    168    DO ib_stream = 1, nb_stream 
    169  
    170       IF( kt == nit000 ) THEN 
    171  
    172          zcount = 0 
    173          ! nn_barotropic must come first 
    174          IF( nn_barotropic .gt. 0 ) THEN          
    175             ! set up information for SSH  
    176             zcount = zcount + 1 
    177             ALLOCATE( bf(ib_stream,zcount)%fnow(jpib,jpjb,1) ) 
    178             IF( ln_tint(ib_stream) ) ALLOCATE( bf(ib_stream,zcount)%fdta(jpib,jpjb,1,2) ) 
    179             blf_i(ib_stream,zcount)%clname = cn_dta(ib_stream)//"_grid_T.nc" 
    180             ... 
    181             ! set up information for U 
    182             zcount = zcount + 1 
    183             ... 
    184             ! set up information for V 
    185             zcount = zcount + 1 
     163   TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   blf_i 
     164 
     165   IF( kt == nit000 ) THEN                ! First call kt=nit000   
     166 
     167      REWIND ( numnam )        
     168      DO ib_set = 1, nb_set    
     169         ! set file information 
     170         cn_dir = './'        ! directory in which the model is executed 
     171         ! ... default values (NB: frequency positive => hours, negative => months) 
     172         !              !  file   ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation  ! 
     173         !              !  name   !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs     ! 
     174         bn_tem      = 'bn_tem'   ,    24     , 'bn_tem' ,   .true.     , .false. , 'daily'     , ''       , '' 
     175         bn_sal      = 'bn_sal'   ,    24     , 'bn_sal' ,   .true.     , .false. , 'daily'     , ''       , '' 
     176         bn_uvel     = 'bn_uvel'  ,    24     , 'bn_uvel',   .true.     , .false. , 'daily'     , ''       , '' 
     177         bn_vvel     = 'bn_vvel'  ,    24     , 'bn_vvel',   .true.     , .false. , 'daily'     , ''       , '' 
     178         bn_ssh      = 'bn_ssh'   ,    24     , 'bn_ssh' ,   .true.     , .false. , 'daily'     , ''       , '' 
     179         bn_ubar     = 'bn_ubar'  ,    24     , 'bn_ubar',   .true.     , .false. , 'daily'     , ''       , '' 
     180         bn_vbar     = 'bn_vbar'  ,    24     , 'bn_vbar',   .true.     , .false. , 'daily'     , ''       , '' 
     181 
     182         READ   ( numnam, namobc_dta )  
     183 
     184         ! Only read in necessary fields for this set. 
     185         zcount = 0         
     186         IF( nn_barotropic(ib_set) .gt. 0 ) THEN 
     187            zcount = zcount+1 ; jp_ssh = zcount 
     188            blf_i(jp_ssh) = bn_ssh 
     189            zcount = zcount+1 ; jp_ubar = zcount 
     190            blf_i(jp_ubar) = bn_ubar 
     191            zcount = zcount+1 ; jp_vbar = zcount 
     192            blf_i(jp_vbar) = bn_vbar 
    186193         ENDIF 
    187          IF ( nn_tra .gt. 0 ) THEN 
    188             ! set up information for T and S 
    189             ... 
    190          ENDIF 
     194         IF( nn_tra(ib_set) .gt. 0 ) THEN 
    191195         .... 
    192              
    193          nn_dta(ib_stream) = zcount 
    194          CALL fld_fill( bf(ib_stream,1:nn_dta(ib_stream)), blf_i(ib_stream,1:nn_dta(ib_stream)), ... ) 
    195        
    196       ENDIF ! kt == nit000 
    197        
    198       IF( PRESENT(jit) && nn_barotropic(ib_stream) .gt. 0 ) THEN 
     196          
     197         nb_dta(ib_set) = zcount 
     198         CALL fld_fill( bf(1:nb_dta(ib_set)), blf_i(ib_set,1:nb_dta(ib_set)), ... ) 
     199 
     200      END DO 
     201   END IF 
     202 
     203   DO ib_set = 1, nb_set    
     204    
     205      IF( PRESENT(jit) ) THEN 
    199206         ! Update barotropic boundary conditions only 
    200207         ! jit is optional argument for fld_read 
    201          CALL fld_read( kt, jit, nn_fobc, bf(ib_stream, 1:3) ) 
     208         IF( nn_barotropic(ib_set) .gt. 0 ) THEN 
     209            CALL fld_read( kt, nn_fobc, bf(ib_set, 1:3), jit=jit ) 
     210         ENDIF 
    202211      ELSE 
    203          CALL fld_read( kt, nn_fobc, bf(ib_stream, 1:nb_dta(ib_stream) ) 
     212         IF ( nn_barotropic(ib_set) .gt. 0 .OR. & 
     213        &     nn_tra(ib_set)        .gt. 0 .OR. & 
     214        &     nn_dyn(ib_set)        .gt. 0 )      THEN 
     215            CALL fld_read( kt, nn_fobc, bf(ib_set, 1:nb_dta(ib_set) ) 
     216         ENDIF 
     217      ENDIF 
     218 
     219      IF( nn_barotropic .gt. 0 ) THEN 
     220         sshbdy(ib_set,:) = bf(ib_set, jp_ssh)%fnow 
     221         ubar(ib_set,:) = bf(ib_set, jp_ubar)%fnow 
     222         ... 
    204223      ENDIF 
    205224       
    206       ! 
    207       ! Update internal boundary data arrays from bf%fnow 
    208       !       
    209  
    210    END DO  ! ib_stream 
     225      IF( .NOT. PRESENT(jit) ) THEN 
     226         IF( nn_tra(ib_set) .gt. 0 ) THEN 
     227         .... 
     228          
     229 
     230   END DO  ! ib_set 
    211231    
    212232   END SUBROUTINE