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 9932 for NEMO/trunk/src/OCE/ICB – NEMO

Ignore:
Timestamp:
2018-07-11T18:12:44+02:00 (6 years ago)
Author:
acc
Message:

Some necessary (but not yet sufficient) changes to iceberg code to reinstate restartability. Details on ticket #2113

Location:
NEMO/trunk/src/OCE/ICB
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/ICB/icb_oce.F90

    r9598 r9932  
    111111   INTEGER , PUBLIC ::   nn_test_icebergs                !: Create icebergs in absence of a restart file from the supplied class nb 
    112112   REAL(wp), PUBLIC, DIMENSION(4) ::   rn_test_box       !: lon1,lon2,lat1,lat2 box to create them in 
     113   LOGICAL , PUBLIC ::   ln_use_calving                  !: Force use of calving data even with nn_test_icebergs > 0  
     114                                                         !  (default is not to use calving data with test bergs) 
    113115   INTEGER , PUBLIC ::   nn_sample_rate                  !: Timesteps between sampling of position for trajectory storage 
    114116   INTEGER , PUBLIC ::   nn_verbose_write                !: timesteps between verbose messages 
  • NEMO/trunk/src/OCE/ICB/icbclv.F90

    r9598 r9932  
    6363      berg_grid%calving_hflx(:,:) = src_calving_hflx(:,:) * tmask_i(:,:) 
    6464 
    65       IF( ll_first_call .AND. .NOT. l_restarted_bergs) THEN      ! This is a hack to simplify initialization 
     65      IF( ll_first_call .AND. .NOT. l_restarted_bergs ) THEN      ! This is a hack to simplify initialization 
    6666         ll_first_call = .FALSE. 
    6767         !do jn=1, nclasses 
     
    100100 
    101101 
    102    SUBROUTINE icb_clv() 
     102   SUBROUTINE icb_clv( kt ) 
    103103      !!---------------------------------------------------------------------- 
    104104      !!                 ***  ROUTINE icb_clv  *** 
     
    114114      !!                is considered 
    115115      !!---------------------------------------------------------------------- 
     116      INTEGER, INTENT(in) ::   kt 
    116117      INTEGER       ::   ji, jj, jn   ! dummy loop indices 
    117118      INTEGER       ::   icnt, icntmax 
  • NEMO/trunk/src/OCE/ICB/icbini.F90

    r9598 r9932  
    228228 
    229229      ! when not generating test icebergs we need to setup calving file 
    230       IF( nn_test_icebergs < 0 ) THEN 
     230      IF( nn_test_icebergs < 0 .OR. ln_use_calving ) THEN 
    231231         ! 
    232232         ! maximum distribution class array does not change in time so read it once 
     
    358358         &              rn_bits_erosion_fraction        , rn_sicn_shift       , ln_passive_mode      ,   & 
    359359         &              ln_time_average_weight          , nn_test_icebergs    , rn_test_box          ,   & 
    360          &              rn_speed_limit , cn_dir, sn_icb 
     360         &              ln_use_calving , rn_speed_limit , cn_dir, sn_icb 
    361361      !!---------------------------------------------------------------------- 
    362362 
     
    399399         IF(lwp) WRITE(numout,*) '   ==>>>   Resetting of nn_test_icebergs to ', nclasses 
    400400         nn_test_icebergs = nclasses 
     401      ENDIF 
     402      ! 
     403      IF( nn_test_icebergs < 0 .AND. .NOT. ln_use_calving ) THEN 
     404         IF(lwp) WRITE(numout,*) 
     405         IF(lwp) WRITE(numout,*) '   ==>>>   Resetting ln_use_calving to .true. since we are not using test icebergs' 
     406         ln_use_calving = .true. 
    401407      ENDIF 
    402408      ! 
     
    440446         WRITE(numout,*) '   Create icebergs in absence of a restart file   nn_test_icebergs  = ', nn_test_icebergs 
    441447         WRITE(numout,*) '                   in lon/lat box                                   = ', rn_test_box 
     448         WRITE(numout,*) '   Use calving data even if nn_test_icebergs > 0    ln_use_calving  = ', ln_use_calving 
    442449         WRITE(numout,*) '   CFL speed limit for a berg            speed_limit                = ', rn_speed_limit 
    443450         WRITE(numout,*) '   Writing Iceberg status information to icebergs.stat file        ' 
  • NEMO/trunk/src/OCE/ICB/icbrst.F90

    r9598 r9932  
    117117         END DO 
    118118         ! 
     119      ELSE 
     120         ibergs_in_file = 0 
    119121      ENDIF  
    120122 
     
    130132      ! Sanity check 
    131133      jn = icb_utl_count() 
    132       IF (nn_verbose_level >= 0)   & 
     134      IF ( lwp .AND. nn_verbose_level >= 0 )   & 
    133135         WRITE(numout,'(2(a,i5))') 'icebergs, read_restart_bergs: # bergs =',jn,' on PE',narea-1 
    134136      IF( lk_mpp ) THEN 
     
    137139         CALL mpp_sum(jn) 
    138140      ENDIF 
    139       IF(lwp)   WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, read_restart_bergs: there were',ibergs_in_file,   & 
     141      IF( lwp )   WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, icb_rst_read: there were',ibergs_in_file,   & 
    140142         &                                    ' bergs in the restart file and', jn,' bergs have been read' 
    141143      ! 
     
    143145      CALL iom_close( ncid ) 
    144146      ! 
    145       IF( lwp .AND. nn_verbose_level >= 0)  WRITE(numout,'(a)') 'icebergs, read_restart_bergs: completed' 
     147      IF( lwp .AND. nn_verbose_level >= 0 )  WRITE(numout,'(a)') 'icebergs, icb_rst_read: completed' 
    146148      ! 
    147149   END SUBROUTINE icb_rst_read 
     
    163165      !!---------------------------------------------------------------------- 
    164166 
    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 
     167      ! Following the normal restart procedure, this routine will be called 
     168      ! the timestep before a restart stage as well as the restart timestep. 
     169      ! This is a performance step enabling the file to be opened and contents 
     170      ! defined in advance of the write. This is not possible with icebergs 
     171      ! since the number of bergs to be written could change between timesteps 
     172      IF( kt == nitrst ) THEN 
     173         ! Only operate on the restart timestep itself. 
     174         ! Assume we write iceberg restarts to same directory as ocean restarts. 
     175         cl_path = TRIM(cn_ocerst_outdir) 
     176         IF( cl_path(LEN_TRIM(cl_path):) /= '/' ) cl_path = TRIM(cl_path) // '/' 
     177         IF( lk_mpp ) THEN 
     178            WRITE(cl_filename,'(A,"_icebergs_",I8.8,"_restart_",I4.4,".nc")') TRIM(cexper), kt, narea-1 
     179         ELSE 
     180            WRITE(cl_filename,'(A,"_icebergs_",I8.8,"_restart.nc")') TRIM(cexper), kt 
     181         ENDIF 
     182         IF ( lwp .AND. nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',  & 
     183           &                                                         TRIM(cl_path)//TRIM(cl_filename) 
     184    
     185         nret = NF90_CREATE(TRIM(cl_path)//TRIM(cl_filename), NF90_CLOBBER, ncid) 
     186         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_create failed') 
     187    
     188         ! Dimensions 
     189         nret = NF90_DEF_DIM(ncid, 'x', jpi, ix_dim) 
     190         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim x failed') 
     191    
     192         nret = NF90_DEF_DIM(ncid, 'y', jpj, iy_dim) 
     193         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim y failed') 
     194    
     195         nret = NF90_DEF_DIM(ncid, 'c', nclasses, nc_dim) 
     196         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim c failed') 
     197    
     198         nret = NF90_DEF_DIM(ncid, 'k', nkounts, ik_dim) 
     199         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim k failed') 
     200    
     201         ! global attributes 
     202         IF( lk_mpp ) THEN 
     203            ! Set domain parameters (assume jpdom_local_full) 
     204            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number_total'   , jpnij              ) 
     205            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number'         , narea-1            ) 
     206            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_dimensions_ids' , (/1     , 2     /) ) 
     207            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_global'    , (/jpiglo, jpjglo/) ) 
     208            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_local'     , (/jpi   , jpj   /) ) 
     209            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_first' , (/nimpp , njmpp /) ) 
     210            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_last'  , (/nimpp + jpi - 1 , njmpp + jpj - 1  /) ) 
     211            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_start', (/nldi - 1        , nldj - 1         /) ) 
     212            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_end'  , (/jpi - nlei      , jpj - nlej       /) ) 
     213            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_type'           , 'BOX'              ) 
     214         ENDIF 
     215          
     216         IF (associated(first_berg)) then 
     217            nret = NF90_DEF_DIM(ncid, 'n', NF90_UNLIMITED, in_dim) 
     218            IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim n failed') 
     219         ENDIF 
     220    
     221         ! Variables 
     222         nret = NF90_DEF_VAR(ncid, 'kount'       , NF90_INT   , (/ ik_dim /), nkountid) 
     223         nret = NF90_DEF_VAR(ncid, 'calving'     , NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvid) 
     224         nret = NF90_DEF_VAR(ncid, 'calving_hflx', NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvhid) 
     225         nret = NF90_DEF_VAR(ncid, 'stored_ice'  , NF90_DOUBLE, (/ ix_dim, iy_dim, nc_dim /), nsiceid) 
     226         nret = NF90_DEF_VAR(ncid, 'stored_heat' , NF90_DOUBLE, (/ ix_dim, iy_dim /), nsheatid) 
     227    
     228         ! Attributes 
     229         nret = NF90_PUT_ATT(ncid, ncalvid , 'long_name', 'iceberg calving') 
     230         nret = NF90_PUT_ATT(ncid, ncalvid , 'units', 'some') 
     231         nret = NF90_PUT_ATT(ncid, ncalvhid, 'long_name', 'heat flux associated with iceberg calving') 
     232         nret = NF90_PUT_ATT(ncid, ncalvhid, 'units', 'some') 
     233         nret = NF90_PUT_ATT(ncid, nsiceid , 'long_name', 'stored ice used to calve icebergs') 
     234         nret = NF90_PUT_ATT(ncid, nsiceid , 'units', 'kg/s') 
     235         nret = NF90_PUT_ATT(ncid, nsheatid, 'long_name', 'heat in stored ice used to calve icebergs') 
     236         nret = NF90_PUT_ATT(ncid, nsheatid, 'units', 'J/kg/s') 
     237    
     238         IF ( ASSOCIATED(first_berg) ) THEN 
     239    
     240            ! Only add berg variables for this PE if we have anything to say 
     241    
     242            ! Variables 
     243            nret = NF90_DEF_VAR(ncid, 'lon', NF90_DOUBLE, in_dim, nlonid) 
     244            nret = NF90_DEF_VAR(ncid, 'lat', NF90_DOUBLE, in_dim, nlatid) 
     245            nret = NF90_DEF_VAR(ncid, 'xi', NF90_DOUBLE, in_dim, nxid) 
     246            nret = NF90_DEF_VAR(ncid, 'yj', NF90_DOUBLE, in_dim, nyid) 
     247            nret = NF90_DEF_VAR(ncid, 'uvel', NF90_DOUBLE, in_dim, nuvelid) 
     248            nret = NF90_DEF_VAR(ncid, 'vvel', NF90_DOUBLE, in_dim, nvvelid) 
     249            nret = NF90_DEF_VAR(ncid, 'mass', NF90_DOUBLE, in_dim, nmassid) 
     250            nret = NF90_DEF_VAR(ncid, 'thickness', NF90_DOUBLE, in_dim, nthicknessid) 
     251            nret = NF90_DEF_VAR(ncid, 'width', NF90_DOUBLE, in_dim, nwidthid) 
     252            nret = NF90_DEF_VAR(ncid, 'length', NF90_DOUBLE, in_dim, nlengthid) 
     253            nret = NF90_DEF_VAR(ncid, 'number', NF90_INT, (/ik_dim,in_dim/), numberid) 
     254            nret = NF90_DEF_VAR(ncid, 'year', NF90_INT, in_dim, nyearid) 
     255            nret = NF90_DEF_VAR(ncid, 'day', NF90_DOUBLE, in_dim, ndayid) 
     256            nret = NF90_DEF_VAR(ncid, 'mass_scaling', NF90_DOUBLE, in_dim, nscaling_id) 
     257            nret = NF90_DEF_VAR(ncid, 'mass_of_bits', NF90_DOUBLE, in_dim, nmass_of_bits_id) 
     258            nret = NF90_DEF_VAR(ncid, 'heat_density', NF90_DOUBLE, in_dim, nheat_density_id) 
     259    
     260            ! Attributes 
     261            nret = NF90_PUT_ATT(ncid, nlonid, 'long_name', 'longitude') 
     262            nret = NF90_PUT_ATT(ncid, nlonid, 'units', 'degrees_E') 
     263            nret = NF90_PUT_ATT(ncid, nlatid, 'long_name', 'latitude') 
     264            nret = NF90_PUT_ATT(ncid, nlatid, 'units', 'degrees_N') 
     265            nret = NF90_PUT_ATT(ncid, nxid, 'long_name', 'x grid box position') 
     266            nret = NF90_PUT_ATT(ncid, nxid, 'units', 'fractional') 
     267            nret = NF90_PUT_ATT(ncid, nyid, 'long_name', 'y grid box position') 
     268            nret = NF90_PUT_ATT(ncid, nyid, 'units', 'fractional') 
     269            nret = NF90_PUT_ATT(ncid, nuvelid, 'long_name', 'zonal velocity') 
     270            nret = NF90_PUT_ATT(ncid, nuvelid, 'units', 'm/s') 
     271            nret = NF90_PUT_ATT(ncid, nvvelid, 'long_name', 'meridional velocity') 
     272            nret = NF90_PUT_ATT(ncid, nvvelid, 'units', 'm/s') 
     273            nret = NF90_PUT_ATT(ncid, nmassid, 'long_name', 'mass') 
     274            nret = NF90_PUT_ATT(ncid, nmassid, 'units', 'kg') 
     275            nret = NF90_PUT_ATT(ncid, nthicknessid, 'long_name', 'thickness') 
     276            nret = NF90_PUT_ATT(ncid, nthicknessid, 'units', 'm') 
     277            nret = NF90_PUT_ATT(ncid, nwidthid, 'long_name', 'width') 
     278            nret = NF90_PUT_ATT(ncid, nwidthid, 'units', 'm') 
     279            nret = NF90_PUT_ATT(ncid, nlengthid, 'long_name', 'length') 
     280            nret = NF90_PUT_ATT(ncid, nlengthid, 'units', 'm') 
     281            nret = NF90_PUT_ATT(ncid, numberid, 'long_name', 'iceberg number on this processor') 
     282            nret = NF90_PUT_ATT(ncid, numberid, 'units', 'count') 
     283            nret = NF90_PUT_ATT(ncid, nyearid, 'long_name', 'calendar year of calving event') 
     284            nret = NF90_PUT_ATT(ncid, nyearid, 'units', 'years') 
     285            nret = NF90_PUT_ATT(ncid, ndayid, 'long_name', 'year day of calving event') 
     286            nret = NF90_PUT_ATT(ncid, ndayid, 'units', 'days') 
     287            nret = NF90_PUT_ATT(ncid, nscaling_id, 'long_name', 'scaling factor for mass of calving berg') 
     288            nret = NF90_PUT_ATT(ncid, nscaling_id, 'units', 'none') 
     289            nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'long_name', 'mass of bergy bits') 
     290            nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'units', 'kg') 
     291            nret = NF90_PUT_ATT(ncid, nheat_density_id, 'long_name', 'heat density') 
     292            nret = NF90_PUT_ATT(ncid, nheat_density_id, 'units', 'J/kg') 
     293    
     294         ENDIF ! associated(first_berg) 
     295    
     296         ! End define mode 
     297         nret = NF90_ENDDEF(ncid) 
     298    
     299         ! -------------------------------- 
     300         ! now write some data 
     301    
     302         nstrt3(1) = 1 
     303         nstrt3(2) = 1 
     304         nlngth3(1) = jpi 
     305         nlngth3(2) = jpj 
     306         nlngth3(3) = 1 
     307    
     308         DO jn=1,nclasses 
     309            griddata(:,:,1) = berg_grid%stored_ice(:,:,jn) 
     310            nstrt3(3) = jn 
     311            nret = NF90_PUT_VAR( ncid, nsiceid, griddata, nstrt3, nlngth3 ) 
     312            IF (nret .ne. NF90_NOERR) THEN 
     313               IF( lwp ) WRITE(numout,*) TRIM(NF90_STRERROR( nret )) 
     314               CALL ctl_stop('icebergs, write_restart: nf_put_var stored_ice failed') 
     315            ENDIF 
     316         ENDDO 
     317         IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_ice  written' 
     318    
     319         nret = NF90_PUT_VAR( ncid, nkountid, num_bergs(:) ) 
     320         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var kount failed') 
     321    
     322         nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
     323         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed') 
     324         IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_heat written' 
     325    
     326         nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(:,:) ) 
     327         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving failed') 
     328         nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(:,:) ) 
     329         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed') 
     330         IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: calving written' 
     331    
     332         IF ( ASSOCIATED(first_berg) ) THEN 
     333    
     334            ! Write variables 
     335            ! just write out the current point of the trajectory 
     336    
     337            this => first_berg 
     338            jn = 0 
     339            DO WHILE (ASSOCIATED(this)) 
     340               pt => this%current_point 
     341               jn=jn+1 
     342    
     343               nret = NF90_PUT_VAR(ncid, numberid, this%number, (/1,jn/), (/nkounts,1/) ) 
     344               nret = NF90_PUT_VAR(ncid, nscaling_id, this%mass_scaling, (/ jn /) ) 
     345    
     346               nret = NF90_PUT_VAR(ncid, nlonid, pt%lon, (/ jn /) ) 
     347               nret = NF90_PUT_VAR(ncid, nlatid, pt%lat, (/ jn /) ) 
     348               nret = NF90_PUT_VAR(ncid, nxid, pt%xi, (/ jn /) ) 
     349               nret = NF90_PUT_VAR(ncid, nyid, pt%yj, (/ jn /) ) 
     350               nret = NF90_PUT_VAR(ncid, nuvelid, pt%uvel, (/ jn /) ) 
     351               nret = NF90_PUT_VAR(ncid, nvvelid, pt%vvel, (/ jn /) ) 
     352               nret = NF90_PUT_VAR(ncid, nmassid, pt%mass, (/ jn /) ) 
     353               nret = NF90_PUT_VAR(ncid, nthicknessid, pt%thickness, (/ jn /) ) 
     354               nret = NF90_PUT_VAR(ncid, nwidthid, pt%width, (/ jn /) ) 
     355               nret = NF90_PUT_VAR(ncid, nlengthid, pt%length, (/ jn /) ) 
     356               nret = NF90_PUT_VAR(ncid, nyearid, pt%year, (/ jn /) ) 
     357               nret = NF90_PUT_VAR(ncid, ndayid, pt%day, (/ jn /) ) 
     358               nret = NF90_PUT_VAR(ncid, nmass_of_bits_id, pt%mass_of_bits, (/ jn /) ) 
     359               nret = NF90_PUT_VAR(ncid, nheat_density_id, pt%heat_density, (/ jn /) ) 
     360    
     361               this=>this%next 
     362            END DO 
     363            ! 
     364         ENDIF ! associated(first_berg) 
     365    
     366         ! Finish up 
     367         nret = NF90_CLOSE(ncid) 
     368         IF (nret /= NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed') 
     369    
     370         ! Sanity check 
     371         jn = icb_utl_count() 
     372         IF ( lwp .AND. nn_verbose_level >= 0)   & 
     373            WRITE(numout,'(2(a,i5))') 'icebergs, icb_rst_write: # bergs =',jn,' on PE',narea-1 
     374         IF( lk_mpp ) THEN 
     375            CALL mpp_sum(jn) 
     376         ENDIF 
     377         IF(lwp)   WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, icb_rst_write: ', jn,   & 
     378            &                                    ' bergs in total have been written at timestep ', kt 
     379         ! 
     380         ! Finish up 
     381         ! 
    172382      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       ! 
    360383   END SUBROUTINE icb_rst_write 
    361384   ! 
  • NEMO/trunk/src/OCE/ICB/icbstp.F90

    r9598 r9932  
    7171      nktberg = kt 
    7272      ! 
    73       IF( nn_test_icebergs < 0 ) THEN    !* read calving data 
     73      IF( nn_test_icebergs < 0 .OR. ln_use_calving ) THEN !* read calving data 
    7474         ! 
    7575         CALL fld_read ( kt, 1, sf_icb ) 
     
    9999                                     CALL icb_clv_flx( kt )   ! Accumulate ice from calving 
    100100      !                              ! 
    101                                      CALL icb_clv()           ! Calve excess stored ice into icebergs 
     101                                     CALL icb_clv( kt )       ! Calve excess stored ice into icebergs 
    102102      !                              ! 
    103103      ! 
Note: See TracChangeset for help on using the changeset viewer.