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 3025 for branches/2011/dev_r2802_UKMET3_rebuild/NEMOGCM/TOOLS/REBUILD_NEMO/src – NEMO

Ignore:
Timestamp:
2011-10-28T17:00:02+02:00 (13 years ago)
Author:
edblockley
Message:

6th commit for rebuild branch; Rewirkign the code to allow time chunk splitting for 4D variables giving the user the option to save memory at the expense of run time. see ticket:#871

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_r2802_UKMET3_rebuild/NEMOGCM/TOOLS/REBUILD_NEMO/src/rebuild_nemo.f90

    r3019 r3025  
    1414   !!     * works for 1,2,3 and 4d arrays or types for all valid NetCDF types 
    1515   !!     * utilises OMP shared memory parallelisation where applicable 
     16   !!     * time 'chunking' for lower memory use  
     17   !!       (only for 4D vars with unlimited dimension) 
    1618   !! 
    1719   !!  Ed Blockley - August 2011 
     
    3638   !!  and errors are written to numerr (default 0 - stderr). 
    3739   !! 
     40   !!  If time chunking is specified the code will use less memory but take a little longer. 
     41   !!  It does this by breaking down the 4D input variables over their 4th dimension  
     42   !!  (generally time) by way of a while loop. 
     43   !! 
    3844   !!------------------------------------------------------------------------------- 
    3945   
     
    6167   CHARACTER(LEN=nf90_max_name), DIMENSION(2) :: dims 
    6268 
    63    INTEGER :: ndomain, ifile, ndomain_file 
     69   INTEGER :: ndomain, ifile, ndomain_file, nchunksize 
    6470   INTEGER :: ncid, outid, idim, istop 
    6571   INTEGER :: natts, attid, xtype, varid, rbdims  
    6672   INTEGER :: jv, ndims, nvars, dimlen, dimids(4) 
    6773   INTEGER :: dimid, unlimitedDimId, di, dj, dr 
     74   INTEGER :: nmax_unlimited, nt, ntchunk  
    6875   INTEGER :: chunksize = 32000000 
    6976   INTEGER :: nthreads = 1 
     
    145152   LOGICAL :: l_findDims = .true. 
    146153 
    147    NAMELIST/nam_rebuild/ filebase, ndomain, dims 
     154   NAMELIST/nam_rebuild/ filebase, ndomain, dims, nchunksize 
    148155 
    149156   !End of definitions  
     
    163170 
    164171   dims(:) = "" 
     172   nchunksize = 0 
    165173   OPEN( UNIT=numnam, FILE='nam_rebuild', FORM='FORMATTED', STATUS='OLD' ) 
    166174   READ( numnam, nam_rebuild ) 
     
    249257      IF( idim == unlimitedDimId ) THEN 
    250258         CALL check_nf90( nf90_def_dim( outid, dimname, nf90_unlimited, dimid) ) 
     259         nmax_unlimited = dimlen 
    251260      ELSE 
    252261         CALL check_nf90( nf90_def_dim( outid, dimname, dimlen, dimid) ) 
     
    336345      l_valid = .false. 
    337346      istop = nf90_noerr 
     347      nt = 1 
     348      ntchunk = nmax_unlimited 
     349      IF( nchunksize == 0 ) nchunksize = nmax_unlimited 
    338350 
    339351!3.2 Inquire variable to find out name and how many dimensions it has 
     
    349361      ENDIF 
    350362 
     363!3.2.0 start while loop for time chunking 
     364 
     365      DO WHILE( nt <= nmax_unlimited ) 
     366 
     367         IF( ndims > 3 ) THEN 
     368            ntchunk = MIN( nchunksize, nmax_unlimited + 1 - nt ) 
     369         ENDIF 
     370 
    351371      IF (l_noRebuild) THEN 
    352372 
    353          IF (l_verbose) WRITE(numout,*) 'Copying data from variable '//TRIM(varname)//'...' 
     373         IF( nchunksize == nmax_unlimited .OR. ndims <= 3 ) THEN 
     374            IF (l_verbose) WRITE(numout,*) 'Copying data from variable '//TRIM(varname)//'...' 
     375         ELSE 
     376            IF (l_verbose) WRITE(numout,'(A,I3,A,I3,A)') ' Copying data from variable '  & 
     377            &                 //TRIM(varname)//' for chunks ',nt,' to ',nt+ntchunk-1,' ...' 
     378         ENDIF 
    354379 
    355380!3.2.1 If rebuilding not required then just need to read in variable 
     
    452477               CASE( NF90_BYTE ) 
    453478                  ALLOCATE(globaldata_4d_i1(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    454                      &                      indimlens(dimids(3)),indimlens(dimids(4)))) 
    455                   CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i1 ) ) 
     479                     &                      indimlens(dimids(3)),ntchunk)) 
     480                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i1, start=(/1,1,1,nt/) ) ) 
    456481               CASE( NF90_SHORT ) 
    457482                  ALLOCATE(globaldata_4d_i2(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    458                      &                      indimlens(dimids(3)),indimlens(dimids(4)))) 
    459                   CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i2 ) ) 
     483                     &                      indimlens(dimids(3)),ntchunk)) 
     484                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i2, start=(/1,1,1,nt/) ) ) 
    460485               CASE( NF90_INT ) 
    461486                  ALLOCATE(globaldata_4d_i4(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    462                      &                      indimlens(dimids(3)),indimlens(dimids(4)))) 
    463                   CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i4 ) ) 
     487                     &                      indimlens(dimids(3)),ntchunk)) 
     488                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i4, start=(/1,1,1,nt/) ) ) 
    464489               CASE( NF90_FLOAT ) 
    465490                  ALLOCATE(globaldata_4d_sp(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    466                      &                      indimlens(dimids(3)),indimlens(dimids(4)))) 
    467                   CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_sp ) ) 
     491                     &                      indimlens(dimids(3)),ntchunk)) 
     492                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_sp, start=(/1,1,1,nt/) ) ) 
    468493               CASE( NF90_DOUBLE ) 
    469494                  ALLOCATE(globaldata_4d_dp(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    470                      &                      indimlens(dimids(3)),indimlens(dimids(4)))) 
    471                   CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_dp ) ) 
     495                     &                      indimlens(dimids(3)),ntchunk)) 
     496                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_dp, start=(/1,1,1,nt/) ) ) 
    472497               CASE DEFAULT 
    473498                  WRITE(numerr,*) 'Unknown nf90 type: ', xtype 
     
    481506!3.2.2 For variables that require rebuilding we need to read in from all ndomain files 
    482507!      Here we allocate global variables ahead of looping over files 
    483          IF (l_verbose) WRITE(numout,*) 'Rebuilding data from variable '//TRIM(varname)//'...' 
    484  
     508         IF( nchunksize == nmax_unlimited .OR. ndims <= 3 ) THEN 
     509            IF (l_verbose) WRITE(numout,*) 'Rebuilding data from variable '//TRIM(varname)//'...' 
     510         ELSE 
     511            IF (l_verbose) WRITE(numout,'(A,I3,A,I3,A)') ' Rebuilding data from variable '  & 
     512            &                 //TRIM(varname)//' for chunks ',nt,' to ',nt+ntchunk-1,' ...' 
     513         ENDIF 
    485514         IF( ndims == 1 ) THEN 
    486515 
     
    547576               CASE( NF90_BYTE ) 
    548577                  ALLOCATE(globaldata_4d_i1(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    549                      &                      outdimlens(dimids(3)),outdimlens(dimids(4)))) 
     578                     &                      outdimlens(dimids(3)),ntchunk)) 
    550579               CASE( NF90_SHORT ) 
    551580                  ALLOCATE(globaldata_4d_i2(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    552                      &                      outdimlens(dimids(3)),outdimlens(dimids(4)))) 
     581                     &                      outdimlens(dimids(3)),ntchunk)) 
    553582               CASE( NF90_INT ) 
    554583                  ALLOCATE(globaldata_4d_i4(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    555                      &                      outdimlens(dimids(3)),outdimlens(dimids(4)))) 
     584                     &                      outdimlens(dimids(3)),ntchunk)) 
    556585               CASE( NF90_FLOAT ) 
    557586                  ALLOCATE(globaldata_4d_sp(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    558                      &                      outdimlens(dimids(3)),outdimlens(dimids(4)))) 
     587                     &                      outdimlens(dimids(3)),ntchunk)) 
    559588               CASE( NF90_DOUBLE ) 
    560589                  ALLOCATE(globaldata_4d_dp(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    561                      &                      outdimlens(dimids(3)),outdimlens(dimids(4)))) 
     590                     &                      outdimlens(dimids(3)),ntchunk)) 
    562591               CASE DEFAULT 
    563592                  WRITE(numerr,*) 'Unknown nf90 type: ', xtype 
     
    584613!$OMP&        globaldata_3d_i2,globaldata_3d_i4,globaldata_3d_sp,globaldata_3d_dp,        & 
    585614!$OMP&        globaldata_4d_i2,globaldata_4d_i4,globaldata_4d_sp,globaldata_4d_dp,        & 
    586 !$OMP&        globaldata_1d_i1,globaldata_2d_i1,globaldata_3d_i1,globaldata_4d_i1) 
     615!$OMP&        globaldata_1d_i1,globaldata_2d_i1,globaldata_3d_i1,globaldata_4d_i1,        & 
     616!$OMP&        ntchunk,nt,nmax_unlimited) 
    587617 
    588618         DO ifile = 1, ndomain 
     
    811841                  CASE( NF90_BYTE ) 
    812842                     ALLOCATE(localdata_4d_i1(local_sizes(di),local_sizes(dj),               & 
    813                          &                     indimlens(dimids(3)),indimlens(dimids(4)))) 
    814                      CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i1 ), istop ) 
     843                         &                     indimlens(dimids(3)),ntchunk)) 
     844                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i1, start=(/1,1,1,nt/) ), istop ) 
    815845!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    816 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i1,localdata_4d_i1,di,dj) 
    817                      DO jl = 1, indimlens(dimids(4)) 
     846!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i1,localdata_4d_i1,di,dj,nt,ntchunk) 
     847                     DO jl = 1, ntchunk 
    818848!$OMP DO  
    819849                        DO jk = 1, indimlens(dimids(3)) 
     
    830860                  CASE( NF90_SHORT ) 
    831861                     ALLOCATE(localdata_4d_i2(local_sizes(di),local_sizes(dj),               & 
    832                         &                     indimlens(dimids(3)),indimlens(dimids(4)))) 
    833                      CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i2 ), istop ) 
     862                        &                     indimlens(dimids(3)),ntchunk)) 
     863                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i2, start=(/1,1,1,nt/) ), istop ) 
    834864!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    835 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i2,localdata_4d_i2,di,dj) 
    836                      DO jl = 1, indimlens(dimids(4)) 
     865!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i2,localdata_4d_i2,di,dj,nt,ntchunk) 
     866                     DO jl = 1, ntchunk 
    837867!$OMP DO  
    838868                        DO jk = 1, indimlens(dimids(3)) 
     
    849879                  CASE( NF90_INT ) 
    850880                     ALLOCATE(localdata_4d_i4(local_sizes(di),local_sizes(dj),               & 
    851                         &                     indimlens(dimids(3)),indimlens(dimids(4)))) 
    852                      CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i4 ), istop ) 
     881                        &                     indimlens(dimids(3)),ntchunk)) 
     882                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i4, start=(/1,1,1,nt/) ), istop ) 
    853883!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    854 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i4,localdata_4d_i4,di,dj) 
    855                      DO jl = 1, indimlens(dimids(4)) 
     884!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i4,localdata_4d_i4,di,dj,nt,ntchunk) 
     885                     DO jl = 1, ntchunk 
    856886!$OMP DO 
    857887                        DO jk = 1, indimlens(dimids(3)) 
     
    868898                  CASE( NF90_FLOAT ) 
    869899                     ALLOCATE(localdata_4d_sp(local_sizes(di),local_sizes(dj),               & 
    870                         &                     indimlens(dimids(3)),indimlens(dimids(4)))) 
    871                      CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_sp ), istop ) 
     900                        &                     indimlens(dimids(3)),ntchunk)) 
     901                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_sp, start=(/1,1,1,nt/) ), istop ) 
    872902!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    873 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_sp,localdata_4d_sp,di,dj)  
    874                      DO jl = 1, indimlens(dimids(4)) 
     903!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_sp,localdata_4d_sp,di,dj,nt,ntchunk)  
     904                     DO jl = 1, ntchunk 
    875905!$OMP DO 
    876906                        DO jk = 1, indimlens(dimids(3)) 
     
    887917                  CASE( NF90_DOUBLE ) 
    888918                     ALLOCATE(localdata_4d_dp(local_sizes(di),local_sizes(dj),               & 
    889                         &                     indimlens(dimids(3)),indimlens(dimids(4)))) 
    890                      CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_dp ), istop ) 
     919                        &                     indimlens(dimids(3)),ntchunk)) 
     920                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_dp, start=(/1,1,1,nt/) ), istop ) 
    891921!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    892 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_dp,localdata_4d_dp,di,dj)  
    893                      DO jl = 1, indimlens(dimids(4)) 
     922!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_dp,localdata_4d_dp,di,dj,nt,ntchunk)  
     923                     DO jl = 1, ntchunk 
    894924!$OMP DO 
    895925                        DO jk = 1, indimlens(dimids(3)) 
     
    10471077     
    10481078      ELSEIF( ndims == 4 ) THEN 
    1049        
     1079 
    10501080         SELECT CASE( xtype )    
    10511081            CASE( NF90_BYTE )                    
    1052                CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_i1 ) ) 
     1082               CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_i1, start=(/1,1,1,nt/) ) ) 
    10531083               DEALLOCATE(globaldata_4d_i1) 
    10541084            CASE( NF90_SHORT )                    
    1055                CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_i2 ) ) 
     1085               CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_i2, start=(/1,1,1,nt/) ) ) 
    10561086               DEALLOCATE(globaldata_4d_i2) 
    10571087            CASE( NF90_INT )                               
    1058                CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_i4 ) ) 
     1088               CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_i4, start=(/1,1,1,nt/) ) ) 
    10591089               DEALLOCATE(globaldata_4d_i4) 
    10601090            CASE( NF90_FLOAT )                               
    1061                CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_sp ) ) 
     1091               CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_sp, start=(/1,1,1,nt/) ) ) 
    10621092               DEALLOCATE(globaldata_4d_sp) 
    10631093            CASE( NF90_DOUBLE )                                          
    1064                CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_dp ) ) 
     1094               CALL check_nf90( nf90_put_var( outid, jv, globaldata_4d_dp, start=(/1,1,1,nt/) ) ) 
    10651095               DEALLOCATE(globaldata_4d_dp) 
    10661096            CASE DEFAULT    
     
    10701100     
    10711101      ENDIF 
     1102 
     1103         nt = nt + ntchunk 
     1104 
     1105      END DO ! WHILE loop 
    10721106     
    10731107   END DO  ! loop over variables 
Note: See TracChangeset for help on using the changeset viewer.