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 10288 for NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/ICB/icbrst.F90 – NEMO

Ignore:
Timestamp:
2018-11-07T18:25:49+01:00 (5 years ago)
Author:
francesca
Message:

reduce global communications, see #2010

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/ICB/icbrst.F90

    r9598 r10288  
    4646   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    4747   !! $Id$ 
    48    !! Software governed by the CeCILL licence     (./LICENSE) 
     48   !! Software governed by the CeCILL license (see ./LICENSE) 
    4949   !!---------------------------------------------------------------------- 
    5050CONTAINS 
     
    6060      INTEGER                      ::   idim, ivar, iatt 
    6161      INTEGER                      ::   jn, iunlim_dim, ibergs_in_file 
    62       INTEGER                      ::   ii,ij,iclass 
     62      INTEGER                      ::   ii, ij, iclass, ibase_err, imax_icb 
    6363      REAL(wp), DIMENSION(nkounts) ::   zdata       
    6464      LOGICAL                      ::   ll_found_restart 
     
    7777      CALL iom_open( TRIM(cl_path)//cl_filename, ncid ) 
    7878 
     79      imax_icb = 0 
    7980      IF( iom_file(ncid)%iduld .GE. 0) THEN 
    8081 
     
    9697               CALL iom_get( ncid, jpdom_unknown, 'number'       , zdata(:) , ktime=jn, kstart=(/1/), kcount=(/nkounts/) ) 
    9798               localberg%number(:) = INT(zdata(:)) 
     99               imax_icb = MAX( imax_icb, INT(zdata(1)) ) 
    98100               CALL iom_get( ncid, 'mass_scaling' , localberg%mass_scaling, ktime=jn ) 
    99101               CALL iom_get( ncid, 'lon'          , localpt%lon           , ktime=jn ) 
     
    117119         END DO 
    118120         ! 
     121      ELSE 
     122         ibergs_in_file = 0 
    119123      ENDIF  
    120124 
     
    127131      CALL iom_get( ncid, jpdom_unknown, 'kount' , zdata(:) ) 
    128132      num_bergs(:) = INT(zdata(:)) 
    129  
    130       ! Sanity check 
     133      ! Close file 
     134      CALL iom_close( ncid ) 
     135      ! 
     136 
     137      ! Sanity checks 
    131138      jn = icb_utl_count() 
    132       IF (nn_verbose_level >= 0)   & 
     139      IF ( lwp .AND. nn_verbose_level >= 0 )   & 
    133140         WRITE(numout,'(2(a,i5))') 'icebergs, read_restart_bergs: # bergs =',jn,' on PE',narea-1 
    134141      IF( lk_mpp ) THEN 
     
    137144         CALL mpp_sum(jn) 
    138145      ENDIF 
    139       IF(lwp)   WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, read_restart_bergs: there were',ibergs_in_file,   & 
     146      IF( lwp )   WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, icb_rst_read: there were',ibergs_in_file,   & 
    140147         &                                    ' bergs in the restart file and', jn,' bergs have been read' 
    141148      ! 
    142       ! Finish up 
    143       CALL iom_close( ncid ) 
    144       ! 
    145       IF( lwp .AND. nn_verbose_level >= 0)  WRITE(numout,'(a)') 'icebergs, read_restart_bergs: completed' 
     149      ! Confirm that all areas have a suitable base for assigning new iceberg 
     150      ! numbers. This will not be the case if restarting from a collated dataset 
     151      ! (even if using the same processor decomposition) 
     152      ! 
     153      ibase_err = 0 
     154      IF( num_bergs(1) < 0 .AND. num_bergs(1) /= narea - jpnij ) THEN 
     155         ! If this area has never calved a new berg then the base should be 
     156         ! set to narea - jpnij. If it is negative but something else then 
     157         ! a new base will be needed to guarantee unique, future iceberg numbers 
     158         ibase_err = 1 
     159      ELSEIF( MOD( num_bergs(1) - narea , jpnij ) /= 0 ) THEN 
     160         ! If this area has a base which is not in the set {narea + N*jpnij} 
     161         ! for positive integers N then a new base will be needed to guarantee  
     162         ! unique, future iceberg numbers 
     163         ibase_err = 1 
     164      ENDIF 
     165      IF( lk_mpp ) THEN 
     166         CALL mpp_sum(ibase_err) 
     167      ENDIF 
     168      IF( ibase_err > 0 ) THEN 
     169         !  
     170         ! A new base is needed. The only secure solution is to set bases such that 
     171         ! all future icebergs numbers will be greater than the current global maximum 
     172         IF( lk_mpp ) THEN 
     173            CALL mpp_max(imax_icb) 
     174         ENDIF 
     175         num_bergs(1) = imax_icb - jpnij + narea 
     176      ENDIF 
     177      ! 
     178      IF( lwp .AND. nn_verbose_level >= 0 )  WRITE(numout,'(a)') 'icebergs, icb_rst_read: completed' 
    146179      ! 
    147180   END SUBROUTINE icb_rst_read 
     
    163196      !!---------------------------------------------------------------------- 
    164197 
    165       ! Assume we write iceberg restarts to same directory as ocean restarts. 
    166       cl_path = TRIM(cn_ocerst_outdir) 
    167       IF( cl_path(LEN_TRIM(cl_path):) /= '/' ) cl_path = TRIM(cl_path) // '/' 
    168       IF( lk_mpp ) THEN 
    169          WRITE(cl_filename,'(A,"_icebergs_",I8.8,"_restart_",I4.4,".nc")') TRIM(cexper), kt, narea-1 
    170       ELSE 
    171          WRITE(cl_filename,'(A,"_icebergs_",I8.8,"_restart.nc")') TRIM(cexper), kt 
     198      ! Following the normal restart procedure, this routine will be called 
     199      ! the timestep before a restart stage as well as the restart timestep. 
     200      ! This is a performance step enabling the file to be opened and contents 
     201      ! defined in advance of the write. This is not possible with icebergs 
     202      ! since the number of bergs to be written could change between timesteps 
     203      IF( kt == nitrst ) THEN 
     204         ! Only operate on the restart timestep itself. 
     205         ! Assume we write iceberg restarts to same directory as ocean restarts. 
     206         cl_path = TRIM(cn_ocerst_outdir) 
     207         IF( cl_path(LEN_TRIM(cl_path):) /= '/' ) cl_path = TRIM(cl_path) // '/' 
     208         IF( lk_mpp ) THEN 
     209            WRITE(cl_filename,'(A,"_icebergs_",I8.8,"_restart_",I4.4,".nc")') TRIM(cexper), kt, narea-1 
     210         ELSE 
     211            WRITE(cl_filename,'(A,"_icebergs_",I8.8,"_restart.nc")') TRIM(cexper), kt 
     212         ENDIF 
     213         IF ( lwp .AND. nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',  & 
     214           &                                                         TRIM(cl_path)//TRIM(cl_filename) 
     215    
     216         nret = NF90_CREATE(TRIM(cl_path)//TRIM(cl_filename), NF90_CLOBBER, ncid) 
     217         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_create failed') 
     218    
     219         ! Dimensions 
     220         nret = NF90_DEF_DIM(ncid, 'x', jpi, ix_dim) 
     221         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim x failed') 
     222    
     223         nret = NF90_DEF_DIM(ncid, 'y', jpj, iy_dim) 
     224         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim y failed') 
     225    
     226         nret = NF90_DEF_DIM(ncid, 'c', nclasses, nc_dim) 
     227         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim c failed') 
     228    
     229         nret = NF90_DEF_DIM(ncid, 'k', nkounts, ik_dim) 
     230         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim k failed') 
     231    
     232         ! global attributes 
     233         IF( lk_mpp ) THEN 
     234            ! Set domain parameters (assume jpdom_local_full) 
     235            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number_total'   , jpnij              ) 
     236            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number'         , narea-1            ) 
     237            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_dimensions_ids' , (/1     , 2     /) ) 
     238            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_global'    , (/jpiglo, jpjglo/) ) 
     239            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_local'     , (/jpi   , jpj   /) ) 
     240            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_first' , (/nimpp , njmpp /) ) 
     241            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_last'  , (/nimpp + jpi - 1 , njmpp + jpj - 1  /) ) 
     242            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_start', (/nldi - 1        , nldj - 1         /) ) 
     243            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_end'  , (/jpi - nlei      , jpj - nlej       /) ) 
     244            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_type'           , 'BOX'              ) 
     245         ENDIF 
     246          
     247         IF (associated(first_berg)) then 
     248            nret = NF90_DEF_DIM(ncid, 'n', NF90_UNLIMITED, in_dim) 
     249            IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim n failed') 
     250         ENDIF 
     251    
     252         ! Variables 
     253         nret = NF90_DEF_VAR(ncid, 'kount'       , NF90_INT   , (/ ik_dim /), nkountid) 
     254         nret = NF90_DEF_VAR(ncid, 'calving'     , NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvid) 
     255         nret = NF90_DEF_VAR(ncid, 'calving_hflx', NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvhid) 
     256         nret = NF90_DEF_VAR(ncid, 'stored_ice'  , NF90_DOUBLE, (/ ix_dim, iy_dim, nc_dim /), nsiceid) 
     257         nret = NF90_DEF_VAR(ncid, 'stored_heat' , NF90_DOUBLE, (/ ix_dim, iy_dim /), nsheatid) 
     258    
     259         ! Attributes 
     260         nret = NF90_PUT_ATT(ncid, ncalvid , 'long_name', 'iceberg calving') 
     261         nret = NF90_PUT_ATT(ncid, ncalvid , 'units', 'some') 
     262         nret = NF90_PUT_ATT(ncid, ncalvhid, 'long_name', 'heat flux associated with iceberg calving') 
     263         nret = NF90_PUT_ATT(ncid, ncalvhid, 'units', 'some') 
     264         nret = NF90_PUT_ATT(ncid, nsiceid , 'long_name', 'stored ice used to calve icebergs') 
     265         nret = NF90_PUT_ATT(ncid, nsiceid , 'units', 'kg/s') 
     266         nret = NF90_PUT_ATT(ncid, nsheatid, 'long_name', 'heat in stored ice used to calve icebergs') 
     267         nret = NF90_PUT_ATT(ncid, nsheatid, 'units', 'J/kg/s') 
     268    
     269         IF ( ASSOCIATED(first_berg) ) THEN 
     270    
     271            ! Only add berg variables for this PE if we have anything to say 
     272    
     273            ! Variables 
     274            nret = NF90_DEF_VAR(ncid, 'lon', NF90_DOUBLE, in_dim, nlonid) 
     275            nret = NF90_DEF_VAR(ncid, 'lat', NF90_DOUBLE, in_dim, nlatid) 
     276            nret = NF90_DEF_VAR(ncid, 'xi', NF90_DOUBLE, in_dim, nxid) 
     277            nret = NF90_DEF_VAR(ncid, 'yj', NF90_DOUBLE, in_dim, nyid) 
     278            nret = NF90_DEF_VAR(ncid, 'uvel', NF90_DOUBLE, in_dim, nuvelid) 
     279            nret = NF90_DEF_VAR(ncid, 'vvel', NF90_DOUBLE, in_dim, nvvelid) 
     280            nret = NF90_DEF_VAR(ncid, 'mass', NF90_DOUBLE, in_dim, nmassid) 
     281            nret = NF90_DEF_VAR(ncid, 'thickness', NF90_DOUBLE, in_dim, nthicknessid) 
     282            nret = NF90_DEF_VAR(ncid, 'width', NF90_DOUBLE, in_dim, nwidthid) 
     283            nret = NF90_DEF_VAR(ncid, 'length', NF90_DOUBLE, in_dim, nlengthid) 
     284            nret = NF90_DEF_VAR(ncid, 'number', NF90_INT, (/ik_dim,in_dim/), numberid) 
     285            nret = NF90_DEF_VAR(ncid, 'year', NF90_INT, in_dim, nyearid) 
     286            nret = NF90_DEF_VAR(ncid, 'day', NF90_DOUBLE, in_dim, ndayid) 
     287            nret = NF90_DEF_VAR(ncid, 'mass_scaling', NF90_DOUBLE, in_dim, nscaling_id) 
     288            nret = NF90_DEF_VAR(ncid, 'mass_of_bits', NF90_DOUBLE, in_dim, nmass_of_bits_id) 
     289            nret = NF90_DEF_VAR(ncid, 'heat_density', NF90_DOUBLE, in_dim, nheat_density_id) 
     290    
     291            ! Attributes 
     292            nret = NF90_PUT_ATT(ncid, nlonid, 'long_name', 'longitude') 
     293            nret = NF90_PUT_ATT(ncid, nlonid, 'units', 'degrees_E') 
     294            nret = NF90_PUT_ATT(ncid, nlatid, 'long_name', 'latitude') 
     295            nret = NF90_PUT_ATT(ncid, nlatid, 'units', 'degrees_N') 
     296            nret = NF90_PUT_ATT(ncid, nxid, 'long_name', 'x grid box position') 
     297            nret = NF90_PUT_ATT(ncid, nxid, 'units', 'fractional') 
     298            nret = NF90_PUT_ATT(ncid, nyid, 'long_name', 'y grid box position') 
     299            nret = NF90_PUT_ATT(ncid, nyid, 'units', 'fractional') 
     300            nret = NF90_PUT_ATT(ncid, nuvelid, 'long_name', 'zonal velocity') 
     301            nret = NF90_PUT_ATT(ncid, nuvelid, 'units', 'm/s') 
     302            nret = NF90_PUT_ATT(ncid, nvvelid, 'long_name', 'meridional velocity') 
     303            nret = NF90_PUT_ATT(ncid, nvvelid, 'units', 'm/s') 
     304            nret = NF90_PUT_ATT(ncid, nmassid, 'long_name', 'mass') 
     305            nret = NF90_PUT_ATT(ncid, nmassid, 'units', 'kg') 
     306            nret = NF90_PUT_ATT(ncid, nthicknessid, 'long_name', 'thickness') 
     307            nret = NF90_PUT_ATT(ncid, nthicknessid, 'units', 'm') 
     308            nret = NF90_PUT_ATT(ncid, nwidthid, 'long_name', 'width') 
     309            nret = NF90_PUT_ATT(ncid, nwidthid, 'units', 'm') 
     310            nret = NF90_PUT_ATT(ncid, nlengthid, 'long_name', 'length') 
     311            nret = NF90_PUT_ATT(ncid, nlengthid, 'units', 'm') 
     312            nret = NF90_PUT_ATT(ncid, numberid, 'long_name', 'iceberg number on this processor') 
     313            nret = NF90_PUT_ATT(ncid, numberid, 'units', 'count') 
     314            nret = NF90_PUT_ATT(ncid, nyearid, 'long_name', 'calendar year of calving event') 
     315            nret = NF90_PUT_ATT(ncid, nyearid, 'units', 'years') 
     316            nret = NF90_PUT_ATT(ncid, ndayid, 'long_name', 'year day of calving event') 
     317            nret = NF90_PUT_ATT(ncid, ndayid, 'units', 'days') 
     318            nret = NF90_PUT_ATT(ncid, nscaling_id, 'long_name', 'scaling factor for mass of calving berg') 
     319            nret = NF90_PUT_ATT(ncid, nscaling_id, 'units', 'none') 
     320            nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'long_name', 'mass of bergy bits') 
     321            nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'units', 'kg') 
     322            nret = NF90_PUT_ATT(ncid, nheat_density_id, 'long_name', 'heat density') 
     323            nret = NF90_PUT_ATT(ncid, nheat_density_id, 'units', 'J/kg') 
     324    
     325         ENDIF ! associated(first_berg) 
     326    
     327         ! End define mode 
     328         nret = NF90_ENDDEF(ncid) 
     329    
     330         ! -------------------------------- 
     331         ! now write some data 
     332    
     333         nstrt3(1) = 1 
     334         nstrt3(2) = 1 
     335         nlngth3(1) = jpi 
     336         nlngth3(2) = jpj 
     337         nlngth3(3) = 1 
     338    
     339         DO jn=1,nclasses 
     340            griddata(:,:,1) = berg_grid%stored_ice(:,:,jn) 
     341            nstrt3(3) = jn 
     342            nret = NF90_PUT_VAR( ncid, nsiceid, griddata, nstrt3, nlngth3 ) 
     343            IF (nret .ne. NF90_NOERR) THEN 
     344               IF( lwp ) WRITE(numout,*) TRIM(NF90_STRERROR( nret )) 
     345               CALL ctl_stop('icebergs, write_restart: nf_put_var stored_ice failed') 
     346            ENDIF 
     347         ENDDO 
     348         IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_ice  written' 
     349    
     350         nret = NF90_PUT_VAR( ncid, nkountid, num_bergs(:) ) 
     351         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var kount failed') 
     352    
     353         nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
     354         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed') 
     355         IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_heat written' 
     356    
     357         nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(:,:) ) 
     358         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving failed') 
     359         nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(:,:) ) 
     360         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed') 
     361         IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: calving written' 
     362    
     363         IF ( ASSOCIATED(first_berg) ) THEN 
     364    
     365            ! Write variables 
     366            ! just write out the current point of the trajectory 
     367    
     368            this => first_berg 
     369            jn = 0 
     370            DO WHILE (ASSOCIATED(this)) 
     371               pt => this%current_point 
     372               jn=jn+1 
     373    
     374               nret = NF90_PUT_VAR(ncid, numberid, this%number, (/1,jn/), (/nkounts,1/) ) 
     375               nret = NF90_PUT_VAR(ncid, nscaling_id, this%mass_scaling, (/ jn /) ) 
     376    
     377               nret = NF90_PUT_VAR(ncid, nlonid, pt%lon, (/ jn /) ) 
     378               nret = NF90_PUT_VAR(ncid, nlatid, pt%lat, (/ jn /) ) 
     379               nret = NF90_PUT_VAR(ncid, nxid, pt%xi, (/ jn /) ) 
     380               nret = NF90_PUT_VAR(ncid, nyid, pt%yj, (/ jn /) ) 
     381               nret = NF90_PUT_VAR(ncid, nuvelid, pt%uvel, (/ jn /) ) 
     382               nret = NF90_PUT_VAR(ncid, nvvelid, pt%vvel, (/ jn /) ) 
     383               nret = NF90_PUT_VAR(ncid, nmassid, pt%mass, (/ jn /) ) 
     384               nret = NF90_PUT_VAR(ncid, nthicknessid, pt%thickness, (/ jn /) ) 
     385               nret = NF90_PUT_VAR(ncid, nwidthid, pt%width, (/ jn /) ) 
     386               nret = NF90_PUT_VAR(ncid, nlengthid, pt%length, (/ jn /) ) 
     387               nret = NF90_PUT_VAR(ncid, nyearid, pt%year, (/ jn /) ) 
     388               nret = NF90_PUT_VAR(ncid, ndayid, pt%day, (/ jn /) ) 
     389               nret = NF90_PUT_VAR(ncid, nmass_of_bits_id, pt%mass_of_bits, (/ jn /) ) 
     390               nret = NF90_PUT_VAR(ncid, nheat_density_id, pt%heat_density, (/ jn /) ) 
     391    
     392               this=>this%next 
     393            END DO 
     394            ! 
     395         ENDIF ! associated(first_berg) 
     396    
     397         ! Finish up 
     398         nret = NF90_CLOSE(ncid) 
     399         IF (nret /= NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed') 
     400    
     401         ! Sanity check 
     402         jn = icb_utl_count() 
     403         IF ( lwp .AND. nn_verbose_level >= 0)   & 
     404            WRITE(numout,'(2(a,i5))') 'icebergs, icb_rst_write: # bergs =',jn,' on PE',narea-1 
     405         IF( lk_mpp ) THEN 
     406            CALL mpp_sum(jn) 
     407         ENDIF 
     408         IF(lwp)   WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, icb_rst_write: ', jn,   & 
     409            &                                    ' bergs in total have been written at timestep ', kt 
     410         ! 
     411         ! Finish up 
     412         ! 
    172413      ENDIF 
    173       IF (nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',TRIM(cl_path)//TRIM(cl_filename) 
    174  
    175       nret = NF90_CREATE(TRIM(cl_path)//TRIM(cl_filename), NF90_CLOBBER, ncid) 
    176       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_create failed') 
    177  
    178       ! Dimensions 
    179       nret = NF90_DEF_DIM(ncid, 'x', jpi, ix_dim) 
    180       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim x failed') 
    181  
    182       nret = NF90_DEF_DIM(ncid, 'y', jpj, iy_dim) 
    183       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim y failed') 
    184  
    185       nret = NF90_DEF_DIM(ncid, 'c', nclasses, nc_dim) 
    186       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim c failed') 
    187  
    188       nret = NF90_DEF_DIM(ncid, 'k', nkounts, ik_dim) 
    189       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim k failed') 
    190  
    191       ! global attributes 
    192       IF( lk_mpp ) THEN 
    193          ! Set domain parameters (assume jpdom_local_full) 
    194          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number_total'   , jpnij              ) 
    195          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number'         , narea-1            ) 
    196          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_dimensions_ids' , (/1     , 2     /) ) 
    197          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_global'    , (/jpiglo, jpjglo/) ) 
    198          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_local'     , (/jpi   , jpj   /) ) 
    199          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_first' , (/nimpp , njmpp /) ) 
    200          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_last'  , (/nimpp + jpi - 1 , njmpp + jpj - 1  /) ) 
    201          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_start', (/nldi - 1        , nldj - 1         /) ) 
    202          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_end'  , (/jpi - nlei      , jpj - nlej       /) ) 
    203          nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_type'           , 'BOX'              ) 
    204       ENDIF 
    205        
    206       IF (associated(first_berg)) then 
    207          nret = NF90_DEF_DIM(ncid, 'n', NF90_UNLIMITED, in_dim) 
    208          IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim n failed') 
    209       ENDIF 
    210  
    211       ! Variables 
    212       nret = NF90_DEF_VAR(ncid, 'kount'       , NF90_INT   , (/ ik_dim /), nkountid) 
    213       nret = NF90_DEF_VAR(ncid, 'calving'     , NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvid) 
    214       nret = NF90_DEF_VAR(ncid, 'calving_hflx', NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvhid) 
    215       nret = NF90_DEF_VAR(ncid, 'stored_ice'  , NF90_DOUBLE, (/ ix_dim, iy_dim, nc_dim /), nsiceid) 
    216       nret = NF90_DEF_VAR(ncid, 'stored_heat' , NF90_DOUBLE, (/ ix_dim, iy_dim /), nsheatid) 
    217  
    218       ! Attributes 
    219       nret = NF90_PUT_ATT(ncid, ncalvid , 'long_name', 'iceberg calving') 
    220       nret = NF90_PUT_ATT(ncid, ncalvid , 'units', 'some') 
    221       nret = NF90_PUT_ATT(ncid, ncalvhid, 'long_name', 'heat flux associated with iceberg calving') 
    222       nret = NF90_PUT_ATT(ncid, ncalvhid, 'units', 'some') 
    223       nret = NF90_PUT_ATT(ncid, nsiceid , 'long_name', 'stored ice used to calve icebergs') 
    224       nret = NF90_PUT_ATT(ncid, nsiceid , 'units', 'kg/s') 
    225       nret = NF90_PUT_ATT(ncid, nsheatid, 'long_name', 'heat in stored ice used to calve icebergs') 
    226       nret = NF90_PUT_ATT(ncid, nsheatid, 'units', 'J/kg/s') 
    227  
    228       IF ( ASSOCIATED(first_berg) ) THEN 
    229  
    230          ! Only add berg variables for this PE if we have anything to say 
    231  
    232          ! Variables 
    233          nret = NF90_DEF_VAR(ncid, 'lon', NF90_DOUBLE, in_dim, nlonid) 
    234          nret = NF90_DEF_VAR(ncid, 'lat', NF90_DOUBLE, in_dim, nlatid) 
    235          nret = NF90_DEF_VAR(ncid, 'xi', NF90_DOUBLE, in_dim, nxid) 
    236          nret = NF90_DEF_VAR(ncid, 'yj', NF90_DOUBLE, in_dim, nyid) 
    237          nret = NF90_DEF_VAR(ncid, 'uvel', NF90_DOUBLE, in_dim, nuvelid) 
    238          nret = NF90_DEF_VAR(ncid, 'vvel', NF90_DOUBLE, in_dim, nvvelid) 
    239          nret = NF90_DEF_VAR(ncid, 'mass', NF90_DOUBLE, in_dim, nmassid) 
    240          nret = NF90_DEF_VAR(ncid, 'thickness', NF90_DOUBLE, in_dim, nthicknessid) 
    241          nret = NF90_DEF_VAR(ncid, 'width', NF90_DOUBLE, in_dim, nwidthid) 
    242          nret = NF90_DEF_VAR(ncid, 'length', NF90_DOUBLE, in_dim, nlengthid) 
    243          nret = NF90_DEF_VAR(ncid, 'number', NF90_INT, (/ik_dim,in_dim/), numberid) 
    244          nret = NF90_DEF_VAR(ncid, 'year', NF90_INT, in_dim, nyearid) 
    245          nret = NF90_DEF_VAR(ncid, 'day', NF90_DOUBLE, in_dim, ndayid) 
    246          nret = NF90_DEF_VAR(ncid, 'mass_scaling', NF90_DOUBLE, in_dim, nscaling_id) 
    247          nret = NF90_DEF_VAR(ncid, 'mass_of_bits', NF90_DOUBLE, in_dim, nmass_of_bits_id) 
    248          nret = NF90_DEF_VAR(ncid, 'heat_density', NF90_DOUBLE, in_dim, nheat_density_id) 
    249  
    250          ! Attributes 
    251          nret = NF90_PUT_ATT(ncid, nlonid, 'long_name', 'longitude') 
    252          nret = NF90_PUT_ATT(ncid, nlonid, 'units', 'degrees_E') 
    253          nret = NF90_PUT_ATT(ncid, nlatid, 'long_name', 'latitude') 
    254          nret = NF90_PUT_ATT(ncid, nlatid, 'units', 'degrees_N') 
    255          nret = NF90_PUT_ATT(ncid, nxid, 'long_name', 'x grid box position') 
    256          nret = NF90_PUT_ATT(ncid, nxid, 'units', 'fractional') 
    257          nret = NF90_PUT_ATT(ncid, nyid, 'long_name', 'y grid box position') 
    258          nret = NF90_PUT_ATT(ncid, nyid, 'units', 'fractional') 
    259          nret = NF90_PUT_ATT(ncid, nuvelid, 'long_name', 'zonal velocity') 
    260          nret = NF90_PUT_ATT(ncid, nuvelid, 'units', 'm/s') 
    261          nret = NF90_PUT_ATT(ncid, nvvelid, 'long_name', 'meridional velocity') 
    262          nret = NF90_PUT_ATT(ncid, nvvelid, 'units', 'm/s') 
    263          nret = NF90_PUT_ATT(ncid, nmassid, 'long_name', 'mass') 
    264          nret = NF90_PUT_ATT(ncid, nmassid, 'units', 'kg') 
    265          nret = NF90_PUT_ATT(ncid, nthicknessid, 'long_name', 'thickness') 
    266          nret = NF90_PUT_ATT(ncid, nthicknessid, 'units', 'm') 
    267          nret = NF90_PUT_ATT(ncid, nwidthid, 'long_name', 'width') 
    268          nret = NF90_PUT_ATT(ncid, nwidthid, 'units', 'm') 
    269          nret = NF90_PUT_ATT(ncid, nlengthid, 'long_name', 'length') 
    270          nret = NF90_PUT_ATT(ncid, nlengthid, 'units', 'm') 
    271          nret = NF90_PUT_ATT(ncid, numberid, 'long_name', 'iceberg number on this processor') 
    272          nret = NF90_PUT_ATT(ncid, numberid, 'units', 'count') 
    273          nret = NF90_PUT_ATT(ncid, nyearid, 'long_name', 'calendar year of calving event') 
    274          nret = NF90_PUT_ATT(ncid, nyearid, 'units', 'years') 
    275          nret = NF90_PUT_ATT(ncid, ndayid, 'long_name', 'year day of calving event') 
    276          nret = NF90_PUT_ATT(ncid, ndayid, 'units', 'days') 
    277          nret = NF90_PUT_ATT(ncid, nscaling_id, 'long_name', 'scaling factor for mass of calving berg') 
    278          nret = NF90_PUT_ATT(ncid, nscaling_id, 'units', 'none') 
    279          nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'long_name', 'mass of bergy bits') 
    280          nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'units', 'kg') 
    281          nret = NF90_PUT_ATT(ncid, nheat_density_id, 'long_name', 'heat density') 
    282          nret = NF90_PUT_ATT(ncid, nheat_density_id, 'units', 'J/kg') 
    283  
    284       ENDIF ! associated(first_berg) 
    285  
    286       ! End define mode 
    287       nret = NF90_ENDDEF(ncid) 
    288  
    289       ! -------------------------------- 
    290       ! now write some data 
    291  
    292       nstrt3(1) = 1 
    293       nstrt3(2) = 1 
    294       nlngth3(1) = jpi 
    295       nlngth3(2) = jpj 
    296       nlngth3(3) = 1 
    297  
    298       DO jn=1,nclasses 
    299          griddata(:,:,1) = berg_grid%stored_ice(:,:,jn) 
    300          nstrt3(3) = jn 
    301          nret = NF90_PUT_VAR( ncid, nsiceid, griddata, nstrt3, nlngth3 ) 
    302          IF (nret .ne. NF90_NOERR) THEN 
    303             IF( lwp ) WRITE(numout,*) TRIM(NF90_STRERROR( nret )) 
    304             CALL ctl_stop('icebergs, write_restart: nf_put_var stored_ice failed') 
    305          ENDIF 
    306       ENDDO 
    307       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_ice  written' 
    308  
    309       nret = NF90_PUT_VAR( ncid, nkountid, num_bergs(:) ) 
    310       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var kount failed') 
    311  
    312       nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
    313       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed') 
    314       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_heat written' 
    315  
    316       nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(:,:) ) 
    317       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving failed') 
    318       nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(:,:) ) 
    319       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed') 
    320       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: calving written' 
    321  
    322       IF ( ASSOCIATED(first_berg) ) THEN 
    323  
    324          ! Write variables 
    325          ! just write out the current point of the trajectory 
    326  
    327          this => first_berg 
    328          jn = 0 
    329          DO WHILE (ASSOCIATED(this)) 
    330             pt => this%current_point 
    331             jn=jn+1 
    332  
    333             nret = NF90_PUT_VAR(ncid, numberid, this%number, (/1,jn/), (/nkounts,1/) ) 
    334             nret = NF90_PUT_VAR(ncid, nscaling_id, this%mass_scaling, (/ jn /) ) 
    335  
    336             nret = NF90_PUT_VAR(ncid, nlonid, pt%lon, (/ jn /) ) 
    337             nret = NF90_PUT_VAR(ncid, nlatid, pt%lat, (/ jn /) ) 
    338             nret = NF90_PUT_VAR(ncid, nxid, pt%xi, (/ jn /) ) 
    339             nret = NF90_PUT_VAR(ncid, nyid, pt%yj, (/ jn /) ) 
    340             nret = NF90_PUT_VAR(ncid, nuvelid, pt%uvel, (/ jn /) ) 
    341             nret = NF90_PUT_VAR(ncid, nvvelid, pt%vvel, (/ jn /) ) 
    342             nret = NF90_PUT_VAR(ncid, nmassid, pt%mass, (/ jn /) ) 
    343             nret = NF90_PUT_VAR(ncid, nthicknessid, pt%thickness, (/ jn /) ) 
    344             nret = NF90_PUT_VAR(ncid, nwidthid, pt%width, (/ jn /) ) 
    345             nret = NF90_PUT_VAR(ncid, nlengthid, pt%length, (/ jn /) ) 
    346             nret = NF90_PUT_VAR(ncid, nyearid, pt%year, (/ jn /) ) 
    347             nret = NF90_PUT_VAR(ncid, ndayid, pt%day, (/ jn /) ) 
    348             nret = NF90_PUT_VAR(ncid, nmass_of_bits_id, pt%mass_of_bits, (/ jn /) ) 
    349             nret = NF90_PUT_VAR(ncid, nheat_density_id, pt%heat_density, (/ jn /) ) 
    350  
    351             this=>this%next 
    352          END DO 
    353          ! 
    354       ENDIF ! associated(first_berg) 
    355  
    356       ! Finish up 
    357       nret = NF90_CLOSE(ncid) 
    358       IF (nret /= NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed') 
    359       ! 
    360414   END SUBROUTINE icb_rst_write 
    361415   ! 
Note: See TracChangeset for help on using the changeset viewer.