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 3370 for branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/ICB/icbrst.F90 – NEMO

Ignore:
Timestamp:
2012-04-30T10:27:44+02:00 (12 years ago)
Author:
sga
Message:

NEMO branch dev_r3337_NOCS10_ICB: lots of cosmetic Gurvanistic changes (the odd space or exclamation mark!)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/ICB/icbrst.F90

    r3361 r3370  
    1414   !!---------------------------------------------------------------------- 
    1515   !!---------------------------------------------------------------------- 
    16    !!   icebergs_read_restart    : initialise 
    17    !!   icebergs_write_restart   : generate test icebergs 
     16   !!   icebergs_read_restart    : initialise                      !!gm suggested name : icebergs_rst_read  or better icb_rst_read 
     17   !!   icebergs_write_restart   : generate test icebergs          !!gm                  icebergs_rst_write or better icb_rst_write 
    1818   !!---------------------------------------------------------------------- 
    1919   USE par_oce        ! NEMO parameters 
     
    2828   PRIVATE 
    2929 
    30    REAL(wp), DIMENSION(:,:,:), PRIVATE, POINTER :: griddata => NULL()    ! need 2d array to read in with 
    31    INTEGER,  DIMENSION(3),     PRIVATE          :: nstrt3, nlngth3 
    32    INTEGER,                    PRIVATE          :: nlonid, nlatid, nxid, nyid, nuvelid, nvvelid 
    33    INTEGER,                    PRIVATE          :: nmassid, nthicknessid, nwidthid, nlengthid 
    34    INTEGER,                    PRIVATE          :: nyearid, ndayid 
    35    INTEGER,                    PRIVATE          :: nscaling_id, nmass_of_bits_id, nheat_density_id, numberid 
    36    INTEGER,                    PRIVATE          :: nsiceid, nsheatid, ncalvid, ncalvhid, nkountid 
    37    INTEGER,                    PRIVATE          :: nret, ncid, nc_dim 
    38  
    39    PUBLIC   icebergs_read_restart       ! routine called in icbini.F90 module 
    40    PUBLIC   icebergs_write_restart      ! routine called in icbrun.F90 module 
    41  
     30   PUBLIC   icebergs_read_restart    ! routine called in icbini.F90 module 
     31   PUBLIC   icebergs_write_restart   ! routine called in icbrun.F90 module 
     32    
     33   INTEGER ::   nlonid, nlatid, nxid, nyid, nuvelid, nvvelid 
     34   INTEGER ::   nmassid, nthicknessid, nwidthid, nlengthid 
     35   INTEGER ::   nyearid, ndayid 
     36   INTEGER ::   nscaling_id, nmass_of_bits_id, nheat_density_id, numberid 
     37   INTEGER ::   nsiceid, nsheatid, ncalvid, ncalvhid, nkountid 
     38   INTEGER ::   nret, ncid, nc_dim 
     39    
     40   INTEGER,  DIMENSION(3)              :: nstrt3, nlngth3 
     41   REAL(wp), DIMENSION(:,:,:), POINTER :: griddata => NULL()    ! need 2d array to read in with 
     42 
     43   !!---------------------------------------------------------------------- 
     44   !! NEMO/OPA 3.3 , NEMO Consortium (2011) 
     45   !! $Id:$ 
     46   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     47   !!---------------------------------------------------------------------- 
    4248CONTAINS 
    4349 
    4450   SUBROUTINE icebergs_read_restart() 
    45       ! sga - read a restart file 
    46       !       for this version, we just read back in the restart for this processor 
    47       !       so we cannot change the processor layout currently with iceberg code 
    48  
    49       ! Local variables 
    50       INTEGER                               ::   idim, ivar, iatt 
    51       INTEGER                               ::   jn, iunlim_dim, ibergs_in_file 
    52       INTEGER                               ::   iclass 
    53       INTEGER, DIMENSION(1)                 ::   istrt, ilngth, idata 
    54       INTEGER, DIMENSION(2)                 ::   istrt2, ilngth2 
    55       INTEGER, DIMENSION(nkounts)           ::   idata2 
    56       REAL(wp), DIMENSION(1)                ::   zdata                                         ! need 1d array to read in with 
     51      !!---------------------------------------------------------------------- 
     52      !!                 ***  SUBROUTINE icebergs_read_restart  *** 
     53      !! 
     54      !! ** Purpose :   read a iceberg restart file 
     55      !!      NB: for this version, we just read back in the restart for this processor 
     56      !!      so we cannot change the processor layout currently with iceberg code 
     57      !!---------------------------------------------------------------------- 
     58      INTEGER                      ::   idim, ivar, iatt 
     59      INTEGER                      ::   jn, iunlim_dim, ibergs_in_file 
     60      INTEGER                      ::   iclass 
     61      INTEGER, DIMENSION(1)        ::   istrt, ilngth, idata 
     62      INTEGER, DIMENSION(2)        ::   istrt2, ilngth2 
     63      INTEGER, DIMENSION(nkounts)  ::   idata2 
     64      REAL(wp), DIMENSION(1)       ::   zdata                                         ! need 1d array to read in with 
    5765                                                                                            ! start and count arrays 
    58       LOGICAL                               ::   ll_found_restart, ll_multiPErestart=.FALSE. 
    59       CHARACTER(len=80)                     ::   cl_filename 
    60       CHARACTER(len=NF90_MAX_NAME)          ::   cl_dname 
    61       TYPE(iceberg)                         ::   localberg ! NOT a pointer but an actual local variable 
    62       TYPE(point)                           ::   localpt   ! NOT a pointer but an actual local variable 
     66      LOGICAL                      ::   ll_found_restart, ll_multiPErestart=.FALSE. 
     67      CHARACTER(len=80)            ::   cl_filename 
     68      CHARACTER(len=NF90_MAX_NAME) ::   cl_dname 
     69      TYPE(iceberg)                ::   localberg ! NOT a pointer but an actual local variable 
     70      TYPE(point)                  ::   localpt   ! NOT a pointer but an actual local variable 
     71      !!---------------------------------------------------------------------- 
    6372 
    6473      IF( .NOT. ASSOCIATED(griddata) ) ALLOCATE( griddata(jpi,jpj,1) ) 
     
    168177            ! 
    169178            CALL add_new_berg_to_list( localberg, localpt ) 
    170          ENDDO 
    171  
     179         END DO 
     180         ! 
    172181      ENDIF 
    173182 
     
    190199      nlngth3(3) = 1 
    191200 
    192       DO jn=1,iclass 
    193  
     201      DO jn = 1, iclass 
    194202         nstrt3(3) = jn 
    195  
    196          nret = NF90_GET_VAR( ncid, nsiceid , griddata, nstrt3, nlngth3 ) 
     203         nret      = NF90_GET_VAR( ncid, nsiceid , griddata, nstrt3, nlngth3 ) 
    197204         berg_grid%stored_ice(:,:,jn) = griddata(:,:,1) 
    198  
    199       ENDDO 
    200  
    201       nret = NF90_GET_VAR( ncid, ncalvid , src_calving(:,:) ) 
    202       nret = NF90_GET_VAR( ncid, ncalvhid, src_calving_hflx(:,:) ) 
     205      END DO 
     206 
     207      nret = NF90_GET_VAR( ncid, ncalvid , src_calving          (:,:) ) 
     208      nret = NF90_GET_VAR( ncid, ncalvhid, src_calving_hflx     (:,:) ) 
    203209      nret = NF90_GET_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
    204210      nret = NF90_GET_VAR( ncid, nkountid, idata2(:) ) 
     
    217223         CALL mpp_sum(jn) 
    218224      ENDIF 
    219       IF ( lwp ) THEN 
    220          WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, read_restart_bergs: there were',ibergs_in_file, & 
    221                                        ' bergs in the restart file and', jn,' bergs have been read' 
    222       ENDIF 
    223  
    224       IF ( lwp .and. nn_verbose_level >= 0)  & 
    225          WRITE(numout,'(a)') 'icebergs, read_restart_bergs: completed' 
    226  
     225      IF(lwp)   WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, read_restart_bergs: there were',ibergs_in_file,   & 
     226         &                                    ' bergs in the restart file and', jn,' bergs have been read' 
     227      ! 
     228      IF( lwp .and. nn_verbose_level >= 0)  WRITE(numout,'(a)') 'icebergs, read_restart_bergs: completed' 
     229      ! 
    227230   END SUBROUTINE icebergs_read_restart 
    228231 
    229 ! ############################################################################## 
    230232 
    231233   SUBROUTINE icebergs_write_restart( kt ) 
    232  
    233       INTEGER, INTENT( in )                 :: kt 
    234       ! Local variables 
    235       INTEGER                               :: ix_dim, iy_dim, ik_dim, in_dim 
    236       INTEGER                               :: jn 
    237       CHARACTER(len=80)                     :: cl_filename 
    238       TYPE(iceberg), POINTER                :: this 
    239       TYPE(point)  , POINTER                :: pt 
     234      !!---------------------------------------------------------------------- 
     235      !!                 ***  SUBROUTINE icebergs_write_restart  *** 
     236      !! 
     237      !!---------------------------------------------------------------------- 
     238      INTEGER, INTENT( in ) :: kt 
     239      ! 
     240      INTEGER ::   jn   ! dummy loop index 
     241      INTEGER ::   ix_dim, iy_dim, ik_dim, in_dim 
     242      CHARACTER(len=80)      :: cl_filename 
     243      TYPE(iceberg), POINTER :: this 
     244      TYPE(point)  , POINTER :: pt 
     245      !!---------------------------------------------------------------------- 
    240246 
    241247      IF( .NOT. ASSOCIATED(griddata) ) ALLOCATE( griddata(jpi,jpj,1) ) 
     
    406412 
    407413            this=>this%next 
    408          ENDDO 
    409  
     414         END DO 
     415         ! 
    410416      ENDIF ! associated(first_berg) 
    411417 
    412418      ! Finish up 
    413419      nret = NF90_CLOSE(ncid) 
    414       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed') 
    415  
     420      IF (nret /= NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed') 
     421      ! 
    416422   END SUBROUTINE icebergs_write_restart 
    417  
     423   ! 
    418424END MODULE icbrst 
Note: See TracChangeset for help on using the changeset viewer.