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

Ignore:
Timestamp:
2012-04-18T12:42:56+02:00 (12 years ago)
Author:
sga
Message:

NEMO branch dev_r3337_NOCS10_ICB: make code conform to NEMO coding conventions

File:
1 edited

Legend:

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

    r3339 r3359  
    2929 
    3030   REAL(wp), DIMENSION(:,:,:), PRIVATE, POINTER :: griddata => NULL()    ! need 2d array to read in with 
    31    INTEGER,  DIMENSION(3),     PRIVATE          :: strt3, lngth3 
    32    INTEGER,                    PRIVATE          :: lonid, latid, xid, yid, uvelid, vvelid 
    33    INTEGER,                    PRIVATE          :: massid, thicknessid, widthid, lengthid 
    34    INTEGER,                    PRIVATE          :: yearid, dayid 
    35    INTEGER,                    PRIVATE          :: scaling_id, mass_of_bits_id, heat_density_id, numberid 
    36    INTEGER,                    PRIVATE          :: siceid, sheatid, calvid, calvhid, kountid 
    37  
    38    PUBLIC   icebergs_read_restart       ! routine called in xxx.F90 module 
    39    PUBLIC   icebergs_write_restart      ! routine called in xxx.F90 module 
     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 
    4041 
    4142CONTAINS 
     
    4748 
    4849      ! Local variables 
    49       INTEGER                               :: ndim, nvar, natt 
    50       INTEGER                               :: k, iret, ncid, unlim_dim, x_dim, y_dim, c_dim, nbergs_in_file 
    51       INTEGER                               :: mclass 
    52       INTEGER, DIMENSION(1)                 :: strt, lngth, idata 
    53       INTEGER, DIMENSION(2)                 :: strt2, lngth2 
    54       INTEGER, DIMENSION(nkounts)           :: idata2 
    55       REAL(wp), DIMENSION(1)                :: data                                         ! need 1d array to read in with 
     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 
    5657                                                                                            ! start and count arrays 
    57       LOGICAL                               :: lres, found_restart, multiPErestart=.FALSE. 
    58       CHARACTER(len=80)                     :: filename 
    59       CHARACTER(len=NF90_MAX_NAME)          :: dname 
    60       TYPE(iceberg)                         :: localberg ! NOT a pointer but an actual local variable 
    61       TYPE(point)                           :: localpt   ! NOT a pointer but an actual local variable 
     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 
    6263 
    6364      IF( .NOT. ASSOCIATED(griddata) ) ALLOCATE( griddata(jpi,jpj,1) ) 
    6465 
    6566      ! Find a restart file 
    66       multiPErestart=.FALSE. 
     67      ll_multiPErestart=.FALSE. 
    6768      DO 
    68          filename = ' ' 
    69          filename = 'restart_icebergs.nc' 
    70          INQUIRE(file=TRIM(filename),exist=found_restart) 
    71          IF (found_restart) EXIT 
    72          filename = ' ' 
    73          WRITE(filename,'("restart_icebergs_",I4.4,".nc")') narea-1 
    74          INQUIRE(file=TRIM(filename),exist=found_restart) 
    75          IF (found_restart) THEN 
    76             multiPErestart=.TRUE. 
     69         cl_filename = ' ' 
     70         cl_filename = 'restart_icebergs.nc' 
     71         INQUIRE( file=TRIM(cl_filename), exist=ll_found_restart ) 
     72         IF ( ll_found_restart ) EXIT 
     73         cl_filename = ' ' 
     74         WRITE( cl_filename, '("restart_icebergs_",I4.4,".nc")' ) narea-1 
     75         INQUIRE( file=TRIM(cl_filename), exist=ll_found_restart ) 
     76         IF ( ll_found_restart ) THEN 
     77            ll_multiPErestart = .TRUE. 
    7778            EXIT 
    7879         ENDIF 
    7980         IF (nn_verbose_level >= 0 .AND. lwp) & 
    80             WRITE(numout,'(a)') 'read_restart_bergs: no restart file found' 
    81          multiPErestart=.TRUE. ! force sanity checking in a multi-PE mode if no file found on this PE 
     81            WRITE( numout, '(a)' ) 'read_restart_bergs: no restart file found' 
     82         ll_multiPErestart = .TRUE.                         ! force checking in a MPP if no file found on this PE 
    8283         EXIT 
    8384      ENDDO 
    8485 
    85       IF ( .NOT. found_restart) THEN ! only do the following if a file was found 
     86      IF ( .NOT. ll_found_restart) THEN                    ! only do the following if a file was found 
    8687         CALL ctl_stop('icebergs: no restart file found') 
    8788      ENDIF 
    8889 
    8990      IF (nn_verbose_level >= 0 .AND. lwp)  & 
    90          WRITE(numout,'(2a)') 'icebergs, read_restart_bergs: found restart file = ',TRIM(filename) 
    91  
    92       iret = NF90_OPEN(TRIM(filename), NF90_NOWRITE, ncid) 
    93       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_open failed') 
    94  
    95       iret = nf90_inquire(ncid, ndim, nvar, natt, unlim_dim) 
    96       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inquire failed') 
    97  
    98       IF( unlim_dim .NE. -1) THEN 
    99  
    100          iret = nf90_inquire_dimension(ncid, unlim_dim, dname, nbergs_in_file) 
    101          IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inq_dimlen failed') 
    102  
    103          iret = NF90_INQ_VARID(ncid, 'number', numberid) 
    104          iret = NF90_INQ_VARID(ncid, 'mass_scaling', scaling_id) 
    105          iret = NF90_INQ_VARID(ncid, 'xi', xid) 
    106          iret = NF90_INQ_VARID(ncid, 'yj', yid) 
    107          iret = NF90_INQ_VARID(ncid, 'lon', lonid) 
    108          iret = NF90_INQ_VARID(ncid, 'lat', latid) 
    109          iret = NF90_INQ_VARID(ncid, 'uvel', uvelid) 
    110          iret = NF90_INQ_VARID(ncid, 'vvel', vvelid) 
    111          iret = NF90_INQ_VARID(ncid, 'mass', massid) 
    112          iret = NF90_INQ_VARID(ncid, 'thickness', thicknessid) 
    113          iret = NF90_INQ_VARID(ncid, 'width', widthid) 
    114          iret = NF90_INQ_VARID(ncid, 'length', lengthid) 
    115          iret = NF90_INQ_VARID(ncid, 'year', yearid) 
    116          iret = NF90_INQ_VARID(ncid, 'day', dayid) 
    117          iret = NF90_INQ_VARID(ncid, 'mass_of_bits', mass_of_bits_id) 
    118          iret = NF90_INQ_VARID(ncid, 'heat_density', heat_density_id) 
    119  
    120          lngth(1) = 1 
    121          strt2(1) = 1 
    122          lngth2(1) = nkounts 
    123          lngth2(2) = 1 
    124          DO k=1, nbergs_in_file 
    125  
    126             strt(1) = k 
    127             strt2(2) = k 
    128  
    129             iret = NF90_GET_VAR(ncid, numberid, idata2, strt2, lngth2 ) 
     91         WRITE(numout,'(2a)') 'icebergs, read_restart_bergs: found restart file = ',TRIM(cl_filename) 
     92 
     93      nret = NF90_OPEN(TRIM(cl_filename), NF90_NOWRITE, ncid) 
     94      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_open failed') 
     95 
     96      nret = nf90_inquire(ncid, idim, ivar, iatt, iunlim_dim) 
     97      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inquire failed') 
     98 
     99      IF( iunlim_dim .NE. -1) THEN 
     100 
     101         nret = nf90_inquire_dimension(ncid, iunlim_dim, cl_dname, ibergs_in_file) 
     102         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inq_dimlen failed') 
     103 
     104         nret = NF90_INQ_VARID(ncid, 'number', numberid) 
     105         nret = NF90_INQ_VARID(ncid, 'mass_scaling', nscaling_id) 
     106         nret = NF90_INQ_VARID(ncid, 'xi', nxid) 
     107         nret = NF90_INQ_VARID(ncid, 'yj', nyid) 
     108         nret = NF90_INQ_VARID(ncid, 'lon', nlonid) 
     109         nret = NF90_INQ_VARID(ncid, 'lat', nlatid) 
     110         nret = NF90_INQ_VARID(ncid, 'uvel', nuvelid) 
     111         nret = NF90_INQ_VARID(ncid, 'vvel', nvvelid) 
     112         nret = NF90_INQ_VARID(ncid, 'mass', nmassid) 
     113         nret = NF90_INQ_VARID(ncid, 'thickness', nthicknessid) 
     114         nret = NF90_INQ_VARID(ncid, 'width', nwidthid) 
     115         nret = NF90_INQ_VARID(ncid, 'length', nlengthid) 
     116         nret = NF90_INQ_VARID(ncid, 'year', nyearid) 
     117         nret = NF90_INQ_VARID(ncid, 'day', ndayid) 
     118         nret = NF90_INQ_VARID(ncid, 'mass_of_bits', nmass_of_bits_id) 
     119         nret = NF90_INQ_VARID(ncid, 'heat_density', nheat_density_id) 
     120 
     121         ilngth(1) = 1 
     122         istrt2(1) = 1 
     123         ilngth2(1) = nkounts 
     124         ilngth2(2) = 1 
     125         DO jn=1, ibergs_in_file 
     126 
     127            istrt(1) = jn 
     128            istrt2(2) = jn 
     129 
     130            nret = NF90_GET_VAR(ncid, numberid, idata2, istrt2, ilngth2 ) 
    130131            localberg%number(:) = idata2(:) 
    131132 
    132             iret = NF90_GET_VAR(ncid, scaling_id, data, strt, lngth ) 
    133             localberg%mass_scaling = data(1) 
    134  
    135             iret = NF90_GET_VAR(ncid, lonid, data, strt, lngth) 
    136             localpt%lon = data(1) 
    137             iret = NF90_GET_VAR(ncid, latid, data, strt, lngth) 
    138             localpt%lat = data(1) 
     133            nret = NF90_GET_VAR(ncid, nscaling_id, zdata, istrt, ilngth ) 
     134            localberg%mass_scaling = zdata(1) 
     135 
     136            nret = NF90_GET_VAR(ncid, nlonid, zdata, istrt, ilngth) 
     137            localpt%lon = zdata(1) 
     138            nret = NF90_GET_VAR(ncid, nlatid, zdata, istrt, ilngth) 
     139            localpt%lat = zdata(1) 
    139140            IF (nn_verbose_level >= 2 .AND. lwp) THEN 
    140                WRITE(numout,'(a,i5,a,2f10.4,a,i5)') 'icebergs, read_restart_bergs: berg ',k,' is at ', & 
     141               WRITE(numout,'(a,i5,a,2f10.4,a,i5)') 'icebergs, read_restart_bergs: berg ',jn,' is at ', & 
    141142                                              localpt%lon,localpt%lat,' on PE ',narea-1 
    142143            ENDIF 
    143             iret = NF90_GET_VAR(ncid, xid, data, strt, lngth) 
    144             localpt%xi = data(1) 
    145             iret = NF90_GET_VAR(ncid, yid, data, strt, lngth) 
    146             localpt%yj = data(1) 
    147             iret = NF90_GET_VAR(ncid, uvelid, data, strt, lngth ) 
    148             localpt%uvel = data(1) 
    149             iret = NF90_GET_VAR(ncid, vvelid, data, strt, lngth ) 
    150             localpt%vvel = data(1) 
    151             iret = NF90_GET_VAR(ncid, massid, data, strt, lngth ) 
    152             localpt%mass = data(1) 
    153             iret = NF90_GET_VAR(ncid, thicknessid, data, strt, lngth ) 
    154             localpt%thickness = data(1) 
    155             iret = NF90_GET_VAR(ncid, widthid, data, strt, lngth ) 
    156             localpt%width = data(1) 
    157             iret = NF90_GET_VAR(ncid, lengthid, data, strt, lngth ) 
    158             localpt%length = data(1) 
    159             iret = NF90_GET_VAR(ncid, yearid, idata, strt, lngth ) 
     144            nret = NF90_GET_VAR(ncid, nxid, zdata, istrt, ilngth) 
     145            localpt%xi = zdata(1) 
     146            nret = NF90_GET_VAR(ncid, nyid, zdata, istrt, ilngth) 
     147            localpt%yj = zdata(1) 
     148            nret = NF90_GET_VAR(ncid, nuvelid, zdata, istrt, ilngth ) 
     149            localpt%uvel = zdata(1) 
     150            nret = NF90_GET_VAR(ncid, nvvelid, zdata, istrt, ilngth ) 
     151            localpt%vvel = zdata(1) 
     152            nret = NF90_GET_VAR(ncid, nmassid, zdata, istrt, ilngth ) 
     153            localpt%mass = zdata(1) 
     154            nret = NF90_GET_VAR(ncid, nthicknessid, zdata, istrt, ilngth ) 
     155            localpt%thickness = zdata(1) 
     156            nret = NF90_GET_VAR(ncid, nwidthid, zdata, istrt, ilngth ) 
     157            localpt%width = zdata(1) 
     158            nret = NF90_GET_VAR(ncid, nlengthid, zdata, istrt, ilngth ) 
     159            localpt%length = zdata(1) 
     160            nret = NF90_GET_VAR(ncid, nyearid, idata, istrt, ilngth ) 
    160161            localpt%year = idata(1) 
    161             iret = NF90_GET_VAR(ncid, dayid, data, strt, lngth ) 
    162             localpt%day = data(1) 
    163             iret = NF90_GET_VAR(ncid, mass_of_bits_id, data, strt, lngth ) 
    164             localpt%mass_of_bits = data(1) 
    165             iret = NF90_GET_VAR(ncid, heat_density_id, data, strt, lngth ) 
    166             localpt%heat_density = data(1) 
     162            nret = NF90_GET_VAR(ncid, ndayid, zdata, istrt, ilngth ) 
     163            localpt%day = zdata(1) 
     164            nret = NF90_GET_VAR(ncid, nmass_of_bits_id, zdata, istrt, ilngth ) 
     165            localpt%mass_of_bits = zdata(1) 
     166            nret = NF90_GET_VAR(ncid, nheat_density_id, zdata, istrt, ilngth ) 
     167            localpt%heat_density = zdata(1) 
    167168            ! 
    168169            CALL add_new_berg_to_list( localberg, localpt ) 
     
    171172      ENDIF 
    172173 
    173       iret = NF90_INQ_DIMID( ncid, 'c', c_dim ) 
    174       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inq_dimid c failed') 
    175  
    176       iret = NF90_INQUIRE_DIMENSION( ncid, c_dim, dname, mclass ) 
    177       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inquire_dimension failed') 
    178  
    179       iret = NF90_INQ_VARID(ncid, 'kount'       , kountid) 
    180       iret = NF90_INQ_VARID(ncid, 'calving'     , calvid) 
    181       iret = NF90_INQ_VARID(ncid, 'calving_hflx', calvhid) 
    182       iret = NF90_INQ_VARID(ncid, 'stored_ice'  , siceid) 
    183       iret = NF90_INQ_VARID(ncid, 'stored_heat' , sheatid) 
    184  
    185       strt3(1) = 1 
    186       strt3(2) = 1 
    187       lngth3(1) = jpi 
    188       lngth3(2) = jpj 
    189       lngth3(3) = 1 
    190  
    191       DO k=1,mclass 
    192  
    193          strt3(3) = k 
    194  
    195          iret = NF90_GET_VAR( ncid, siceid , griddata, strt3, lngth3 ) 
    196          berg_grid%stored_ice(:,:,k) = griddata(:,:,1) 
     174      nret = NF90_INQ_DIMID( ncid, 'c', nc_dim ) 
     175      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inq_dimid c failed') 
     176 
     177      nret = NF90_INQUIRE_DIMENSION( ncid, nc_dim, cl_dname, iclass ) 
     178      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inquire_dimension failed') 
     179 
     180      nret = NF90_INQ_VARID(ncid, 'kount'       , nkountid) 
     181      nret = NF90_INQ_VARID(ncid, 'calving'     , ncalvid) 
     182      nret = NF90_INQ_VARID(ncid, 'calving_hflx', ncalvhid) 
     183      nret = NF90_INQ_VARID(ncid, 'stored_ice'  , nsiceid) 
     184      nret = NF90_INQ_VARID(ncid, 'stored_heat' , nsheatid) 
     185 
     186      nstrt3(1) = 1 
     187      nstrt3(2) = 1 
     188      nlngth3(1) = jpi 
     189      nlngth3(2) = jpj 
     190      nlngth3(3) = 1 
     191 
     192      DO jn=1,iclass 
     193 
     194         nstrt3(3) = jn 
     195 
     196         nret = NF90_GET_VAR( ncid, nsiceid , griddata, nstrt3, nlngth3 ) 
     197         berg_grid%stored_ice(:,:,jn) = griddata(:,:,1) 
    197198 
    198199      ENDDO 
    199200 
    200       iret = NF90_GET_VAR( ncid, calvid , p_calving(:,:) ) 
    201       iret = NF90_GET_VAR( ncid, calvhid, p_calving_hflx(:,:) ) 
    202       iret = NF90_GET_VAR( ncid, sheatid, berg_grid%stored_heat(:,:) ) 
    203       iret = NF90_GET_VAR( ncid, kountid, idata2(:) ) 
    204       kount_bergs(:) = idata2(:) 
     201      nret = NF90_GET_VAR( ncid, ncalvid , src_calving(:,:) ) 
     202      nret = NF90_GET_VAR( ncid, ncalvhid, src_calving_hflx(:,:) ) 
     203      nret = NF90_GET_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
     204      nret = NF90_GET_VAR( ncid, nkountid, idata2(:) ) 
     205      num_bergs(:) = idata2(:) 
    205206 
    206207      ! Finish up 
    207       iret = NF90_CLOSE(ncid) 
    208       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_close failed') 
     208      nret = NF90_CLOSE(ncid) 
     209      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_close failed') 
    209210 
    210211      ! Sanity check 
    211       k = count_bergs() 
     212      jn = count_bergs() 
    212213      IF (nn_verbose_level >= 0)   & 
    213          WRITE(numout,'(2(a,i5))') 'icebergs, read_restart_bergs: # bergs =',k,' on PE',narea-1 
     214         WRITE(numout,'(2(a,i5))') 'icebergs, read_restart_bergs: # bergs =',jn,' on PE',narea-1 
    214215      IF( lk_mpp ) THEN 
    215          IF (multiPErestart) CALL mpp_sum(nbergs_in_file) ! In case PE 0 didn't open a file 
    216          CALL mpp_sum(k) 
     216         IF (ll_multiPErestart) CALL mpp_sum(ibergs_in_file) ! In case PE 0 didn't open a file 
     217         CALL mpp_sum(jn) 
    217218      ENDIF 
    218219      IF ( lwp ) THEN 
    219          WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, read_restart_bergs: there were',nbergs_in_file, & 
    220                                        ' bergs in the restart file and', k,' bergs have been read' 
     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' 
    221222      ENDIF 
    222223 
     
    232233      INTEGER, INTENT( in )                 :: kt 
    233234      ! Local variables 
    234       INTEGER                               :: iret, ncid, k_dim, n_dim, x_dim, y_dim, c_dim, k 
    235       CHARACTER(len=80)                     :: filename 
     235      INTEGER,                              :: ix_dim, iy_dim, ik_dim, in_dim 
     236      INTEGER                               :: jn 
     237      CHARACTER(len=80)                     :: cl_filename 
    236238      TYPE(iceberg), POINTER                :: this 
    237239      TYPE(point)  , POINTER                :: pt 
     
    239241      IF( .NOT. ASSOCIATED(griddata) ) ALLOCATE( griddata(jpi,jpj,1) ) 
    240242 
    241       WRITE(filename,'("icebergs_",I8.8,"_restart_",I4.4,".nc")') kt, narea-1 
    242       IF (nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',TRIM(filename) 
    243  
    244       iret = NF90_CREATE(TRIM(filename), NF90_CLOBBER, ncid) 
    245       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_create failed') 
     243      WRITE(cl_filename,'("icebergs_",I8.8,"_restart_",I4.4,".nc")') kt, narea-1 
     244      IF (nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',TRIM(cl_filename) 
     245 
     246      nret = NF90_CREATE(TRIM(cl_filename), NF90_CLOBBER, ncid) 
     247      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_create failed') 
    246248 
    247249      ! Dimensions 
    248       iret = NF90_DEF_DIM(ncid, 'x', jpi, x_dim) 
    249       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim x failed') 
    250  
    251       iret = NF90_DEF_DIM(ncid, 'y', jpj, y_dim) 
    252       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim y failed') 
    253  
    254       iret = NF90_DEF_DIM(ncid, 'c', nclasses, c_dim) 
    255       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim c failed') 
    256  
    257       iret = NF90_DEF_DIM(ncid, 'k', nkounts, k_dim) 
    258       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim k failed') 
     250      nret = NF90_DEF_DIM(ncid, 'x', jpi, ix_dim) 
     251      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim x failed') 
     252 
     253      nret = NF90_DEF_DIM(ncid, 'y', jpj, iy_dim) 
     254      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim y failed') 
     255 
     256      nret = NF90_DEF_DIM(ncid, 'c', nclasses, nc_dim) 
     257      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim c failed') 
     258 
     259      nret = NF90_DEF_DIM(ncid, 'k', nkounts, ik_dim) 
     260      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim k failed') 
    259261 
    260262      IF (associated(first_berg)) then 
    261          iret = NF90_DEF_DIM(ncid, 'n', NF90_UNLIMITED, n_dim) 
    262          IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim n failed') 
     263         nret = NF90_DEF_DIM(ncid, 'n', NF90_UNLIMITED, in_dim) 
     264         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim n failed') 
    263265      ENDIF 
    264266 
    265267      ! Variables 
    266       iret = NF90_DEF_VAR(ncid, 'kount'       , NF90_INT   , (/ k_dim /), kountid) 
    267       iret = NF90_DEF_VAR(ncid, 'calving'     , NF90_DOUBLE, (/ x_dim, y_dim /), calvid) 
    268       iret = NF90_DEF_VAR(ncid, 'calving_hflx', NF90_DOUBLE, (/ x_dim, y_dim /), calvhid) 
    269       iret = NF90_DEF_VAR(ncid, 'stored_ice'  , NF90_DOUBLE, (/ x_dim, y_dim, c_dim /), siceid) 
    270       iret = NF90_DEF_VAR(ncid, 'stored_heat' , NF90_DOUBLE, (/ x_dim, y_dim /), sheatid) 
     268      nret = NF90_DEF_VAR(ncid, 'kount'       , NF90_INT   , (/ ik_dim /), nkountid) 
     269      nret = NF90_DEF_VAR(ncid, 'calving'     , NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvid) 
     270      nret = NF90_DEF_VAR(ncid, 'calving_hflx', NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvhid) 
     271      nret = NF90_DEF_VAR(ncid, 'stored_ice'  , NF90_DOUBLE, (/ ix_dim, iy_dim, nc_dim /), nsiceid) 
     272      nret = NF90_DEF_VAR(ncid, 'stored_heat' , NF90_DOUBLE, (/ ix_dim, iy_dim /), nsheatid) 
    271273 
    272274      ! Attributes 
    273       iret = NF90_PUT_ATT(ncid, calvid , 'long_name', 'iceberg calving') 
    274       iret = NF90_PUT_ATT(ncid, calvid , 'units', 'some') 
    275       iret = NF90_PUT_ATT(ncid, calvhid, 'long_name', 'heat flux associated with iceberg calving') 
    276       iret = NF90_PUT_ATT(ncid, calvhid, 'units', 'some') 
    277       iret = NF90_PUT_ATT(ncid, siceid , 'long_name', 'stored ice used to calve icebergs') 
    278       iret = NF90_PUT_ATT(ncid, siceid , 'units', 'kg/s') 
    279       iret = NF90_PUT_ATT(ncid, sheatid, 'long_name', 'heat in stored ice used to calve icebergs') 
    280       iret = NF90_PUT_ATT(ncid, sheatid, 'units', 'J/kg/s') 
     275      nret = NF90_PUT_ATT(ncid, ncalvid , 'long_name', 'iceberg calving') 
     276      nret = NF90_PUT_ATT(ncid, ncalvid , 'units', 'some') 
     277      nret = NF90_PUT_ATT(ncid, ncalvhid, 'long_name', 'heat flux associated with iceberg calving') 
     278      nret = NF90_PUT_ATT(ncid, ncalvhid, 'units', 'some') 
     279      nret = NF90_PUT_ATT(ncid, nsiceid , 'long_name', 'stored ice used to calve icebergs') 
     280      nret = NF90_PUT_ATT(ncid, nsiceid , 'units', 'kg/s') 
     281      nret = NF90_PUT_ATT(ncid, nsheatid, 'long_name', 'heat in stored ice used to calve icebergs') 
     282      nret = NF90_PUT_ATT(ncid, nsheatid, 'units', 'J/kg/s') 
    281283 
    282284      IF ( ASSOCIATED(first_berg) ) THEN 
     
    285287 
    286288         ! Variables 
    287          iret = NF90_DEF_VAR(ncid, 'lon', NF90_DOUBLE, n_dim, lonid) 
    288          iret = NF90_DEF_VAR(ncid, 'lat', NF90_DOUBLE, n_dim, latid) 
    289          iret = NF90_DEF_VAR(ncid, 'xi', NF90_DOUBLE, n_dim, xid) 
    290          iret = NF90_DEF_VAR(ncid, 'yj', NF90_DOUBLE, n_dim, yid) 
    291          iret = NF90_DEF_VAR(ncid, 'uvel', NF90_DOUBLE, n_dim, uvelid) 
    292          iret = NF90_DEF_VAR(ncid, 'vvel', NF90_DOUBLE, n_dim, vvelid) 
    293          iret = NF90_DEF_VAR(ncid, 'mass', NF90_DOUBLE, n_dim, massid) 
    294          iret = NF90_DEF_VAR(ncid, 'thickness', NF90_DOUBLE, n_dim, thicknessid) 
    295          iret = NF90_DEF_VAR(ncid, 'width', NF90_DOUBLE, n_dim, widthid) 
    296          iret = NF90_DEF_VAR(ncid, 'length', NF90_DOUBLE, n_dim, lengthid) 
    297          iret = NF90_DEF_VAR(ncid, 'number', NF90_INT, (/k_dim,n_dim/), numberid) 
    298          iret = NF90_DEF_VAR(ncid, 'year', NF90_INT, n_dim, yearid) 
    299          iret = NF90_DEF_VAR(ncid, 'day', NF90_DOUBLE, n_dim, dayid) 
    300          iret = NF90_DEF_VAR(ncid, 'mass_scaling', NF90_DOUBLE, n_dim, scaling_id) 
    301          iret = NF90_DEF_VAR(ncid, 'mass_of_bits', NF90_DOUBLE, n_dim, mass_of_bits_id) 
    302          iret = NF90_DEF_VAR(ncid, 'heat_density', NF90_DOUBLE, n_dim, heat_density_id) 
     289         nret = NF90_DEF_VAR(ncid, 'lon', NF90_DOUBLE, in_dim, nlonid) 
     290         nret = NF90_DEF_VAR(ncid, 'lat', NF90_DOUBLE, in_dim, nlatid) 
     291         nret = NF90_DEF_VAR(ncid, 'xi', NF90_DOUBLE, in_dim, nxid) 
     292         nret = NF90_DEF_VAR(ncid, 'yj', NF90_DOUBLE, in_dim, nyid) 
     293         nret = NF90_DEF_VAR(ncid, 'uvel', NF90_DOUBLE, in_dim, nuvelid) 
     294         nret = NF90_DEF_VAR(ncid, 'vvel', NF90_DOUBLE, in_dim, nvvelid) 
     295         nret = NF90_DEF_VAR(ncid, 'mass', NF90_DOUBLE, in_dim, nmassid) 
     296         nret = NF90_DEF_VAR(ncid, 'thickness', NF90_DOUBLE, in_dim, nthicknessid) 
     297         nret = NF90_DEF_VAR(ncid, 'width', NF90_DOUBLE, in_dim, nwidthid) 
     298         nret = NF90_DEF_VAR(ncid, 'length', NF90_DOUBLE, in_dim, nlengthid) 
     299         nret = NF90_DEF_VAR(ncid, 'number', NF90_INT, (/ik_dim,in_dim/), numberid) 
     300         nret = NF90_DEF_VAR(ncid, 'year', NF90_INT, in_dim, nyearid) 
     301         nret = NF90_DEF_VAR(ncid, 'day', NF90_DOUBLE, in_dim, ndayid) 
     302         nret = NF90_DEF_VAR(ncid, 'mass_scaling', NF90_DOUBLE, in_dim, nscaling_id) 
     303         nret = NF90_DEF_VAR(ncid, 'mass_of_bits', NF90_DOUBLE, in_dim, nmass_of_bits_id) 
     304         nret = NF90_DEF_VAR(ncid, 'heat_density', NF90_DOUBLE, in_dim, nheat_density_id) 
    303305 
    304306         ! Attributes 
    305          iret = NF90_PUT_ATT(ncid, lonid, 'long_name', 'longitude') 
    306          iret = NF90_PUT_ATT(ncid, lonid, 'units', 'degrees_E') 
    307          iret = NF90_PUT_ATT(ncid, latid, 'long_name', 'latitude') 
    308          iret = NF90_PUT_ATT(ncid, latid, 'units', 'degrees_N') 
    309          iret = NF90_PUT_ATT(ncid, xid, 'long_name', 'x grid box position') 
    310          iret = NF90_PUT_ATT(ncid, xid, 'units', 'fractional') 
    311          iret = NF90_PUT_ATT(ncid, yid, 'long_name', 'y grid box position') 
    312          iret = NF90_PUT_ATT(ncid, yid, 'units', 'fractional') 
    313          iret = NF90_PUT_ATT(ncid, uvelid, 'long_name', 'zonal velocity') 
    314          iret = NF90_PUT_ATT(ncid, uvelid, 'units', 'm/s') 
    315          iret = NF90_PUT_ATT(ncid, vvelid, 'long_name', 'meridional velocity') 
    316          iret = NF90_PUT_ATT(ncid, vvelid, 'units', 'm/s') 
    317          iret = NF90_PUT_ATT(ncid, massid, 'long_name', 'mass') 
    318          iret = NF90_PUT_ATT(ncid, massid, 'units', 'kg') 
    319          iret = NF90_PUT_ATT(ncid, thicknessid, 'long_name', 'thickness') 
    320          iret = NF90_PUT_ATT(ncid, thicknessid, 'units', 'm') 
    321          iret = NF90_PUT_ATT(ncid, widthid, 'long_name', 'width') 
    322          iret = NF90_PUT_ATT(ncid, widthid, 'units', 'm') 
    323          iret = NF90_PUT_ATT(ncid, lengthid, 'long_name', 'length') 
    324          iret = NF90_PUT_ATT(ncid, lengthid, 'units', 'm') 
    325          iret = NF90_PUT_ATT(ncid, numberid, 'long_name', 'iceberg number on this processor') 
    326          iret = NF90_PUT_ATT(ncid, numberid, 'units', 'count') 
    327          iret = NF90_PUT_ATT(ncid, yearid, 'long_name', 'calendar year of calving event') 
    328          iret = NF90_PUT_ATT(ncid, yearid, 'units', 'years') 
    329          iret = NF90_PUT_ATT(ncid, dayid, 'long_name', 'year day of calving event') 
    330          iret = NF90_PUT_ATT(ncid, dayid, 'units', 'days') 
    331          iret = NF90_PUT_ATT(ncid, scaling_id, 'long_name', 'scaling factor for mass of calving berg') 
    332          iret = NF90_PUT_ATT(ncid, scaling_id, 'units', 'none') 
    333          iret = NF90_PUT_ATT(ncid, mass_of_bits_id, 'long_name', 'mass of bergy bits') 
    334          iret = NF90_PUT_ATT(ncid, mass_of_bits_id, 'units', 'kg') 
    335          iret = NF90_PUT_ATT(ncid, heat_density_id, 'long_name', 'heat density') 
    336          iret = NF90_PUT_ATT(ncid, heat_density_id, 'units', 'J/kg') 
     307         nret = NF90_PUT_ATT(ncid, nlonid, 'long_name', 'longitude') 
     308         nret = NF90_PUT_ATT(ncid, nlonid, 'units', 'degrees_E') 
     309         nret = NF90_PUT_ATT(ncid, nlatid, 'long_name', 'latitude') 
     310         nret = NF90_PUT_ATT(ncid, nlatid, 'units', 'degrees_N') 
     311         nret = NF90_PUT_ATT(ncid, nxid, 'long_name', 'x grid box position') 
     312         nret = NF90_PUT_ATT(ncid, nxid, 'units', 'fractional') 
     313         nret = NF90_PUT_ATT(ncid, nyid, 'long_name', 'y grid box position') 
     314         nret = NF90_PUT_ATT(ncid, nyid, 'units', 'fractional') 
     315         nret = NF90_PUT_ATT(ncid, nuvelid, 'long_name', 'zonal velocity') 
     316         nret = NF90_PUT_ATT(ncid, nuvelid, 'units', 'm/s') 
     317         nret = NF90_PUT_ATT(ncid, nvvelid, 'long_name', 'meridional velocity') 
     318         nret = NF90_PUT_ATT(ncid, nvvelid, 'units', 'm/s') 
     319         nret = NF90_PUT_ATT(ncid, nmassid, 'long_name', 'mass') 
     320         nret = NF90_PUT_ATT(ncid, nmassid, 'units', 'kg') 
     321         nret = NF90_PUT_ATT(ncid, nthicknessid, 'long_name', 'thickness') 
     322         nret = NF90_PUT_ATT(ncid, nthicknessid, 'units', 'm') 
     323         nret = NF90_PUT_ATT(ncid, nwidthid, 'long_name', 'width') 
     324         nret = NF90_PUT_ATT(ncid, nwidthid, 'units', 'm') 
     325         nret = NF90_PUT_ATT(ncid, nlengthid, 'long_name', 'length') 
     326         nret = NF90_PUT_ATT(ncid, nlengthid, 'units', 'm') 
     327         nret = NF90_PUT_ATT(ncid, numberid, 'long_name', 'iceberg number on this processor') 
     328         nret = NF90_PUT_ATT(ncid, numberid, 'units', 'count') 
     329         nret = NF90_PUT_ATT(ncid, nyearid, 'long_name', 'calendar year of calving event') 
     330         nret = NF90_PUT_ATT(ncid, nyearid, 'units', 'years') 
     331         nret = NF90_PUT_ATT(ncid, ndayid, 'long_name', 'year day of calving event') 
     332         nret = NF90_PUT_ATT(ncid, ndayid, 'units', 'days') 
     333         nret = NF90_PUT_ATT(ncid, nscaling_id, 'long_name', 'scaling factor for mass of calving berg') 
     334         nret = NF90_PUT_ATT(ncid, nscaling_id, 'units', 'none') 
     335         nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'long_name', 'mass of bergy bits') 
     336         nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'units', 'kg') 
     337         nret = NF90_PUT_ATT(ncid, nheat_density_id, 'long_name', 'heat density') 
     338         nret = NF90_PUT_ATT(ncid, nheat_density_id, 'units', 'J/kg') 
    337339 
    338340      ENDIF ! associated(first_berg) 
    339341 
    340342      ! End define mode 
    341       iret = NF90_ENDDEF(ncid) 
     343      nret = NF90_ENDDEF(ncid) 
    342344 
    343345      ! -------------------------------- 
    344346      ! now write some data 
    345347 
    346       strt3(1) = 1 
    347       strt3(2) = 1 
    348       lngth3(1) = jpi 
    349       lngth3(2) = jpj 
    350       lngth3(3) = 1 
    351  
    352       DO k=1,nclasses 
    353          griddata(:,:,1) = berg_grid%stored_ice(:,:,k) 
    354          strt3(3) = k 
    355          iret = NF90_PUT_VAR( ncid, siceid, griddata, strt3, lngth3 ) 
    356          IF (iret .ne. NF90_NOERR) THEN 
    357             IF( lwp ) WRITE(numout,*) TRIM(NF90_STRERROR( iret )) 
     348      nstrt3(1) = 1 
     349      nstrt3(2) = 1 
     350      nlngth3(1) = jpi 
     351      nlngth3(2) = jpj 
     352      nlngth3(3) = 1 
     353 
     354      DO jn=1,nclasses 
     355         griddata(:,:,1) = berg_grid%stored_ice(:,:,jn) 
     356         nstrt3(3) = jn 
     357         nret = NF90_PUT_VAR( ncid, nsiceid, griddata, nstrt3, nlngth3 ) 
     358         IF (nret .ne. NF90_NOERR) THEN 
     359            IF( lwp ) WRITE(numout,*) TRIM(NF90_STRERROR( nret )) 
    358360            CALL ctl_stop('icebergs, write_restart: nf_put_var stored_ice failed') 
    359361         ENDIF 
    360362      ENDDO 
    361       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(filename),' var: stored_ice  written' 
    362  
    363       iret = NF90_PUT_VAR( ncid, kountid, kount_bergs(:) ) 
    364       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var kount failed') 
    365  
    366       iret = NF90_PUT_VAR( ncid, sheatid, berg_grid%stored_heat(:,:) ) 
    367       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed') 
    368       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(filename),' var: stored_heat written' 
    369  
    370       iret = NF90_PUT_VAR( ncid, calvid , p_calving(:,:) ) 
    371       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving failed') 
    372       iret = NF90_PUT_VAR( ncid, calvhid, p_calving_hflx(:,:) ) 
    373       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed') 
    374       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(filename),' var: calving written' 
     363      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: stored_ice  written' 
     364 
     365      nret = NF90_PUT_VAR( ncid, nkountid, num_bergs(:) ) 
     366      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var kount failed') 
     367 
     368      nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
     369      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed') 
     370      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: stored_heat written' 
     371 
     372      nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(:,:) ) 
     373      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving failed') 
     374      nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(:,:) ) 
     375      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed') 
     376      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: calving written' 
    375377 
    376378      IF ( ASSOCIATED(first_berg) ) THEN 
    377379 
    378380         ! Write variables 
    379          ! sga - just write out the current point of the trajectory 
     381         ! just write out the current point of the trajectory 
    380382 
    381383         this => first_berg 
    382          k = 0 
     384         jn = 0 
    383385         DO WHILE (ASSOCIATED(this)) 
    384386            pt => this%current_point 
    385             k=k+1 
    386  
    387             iret = NF90_PUT_VAR(ncid, numberid, this%number, (/1,k/), (/nkounts,1/) ) 
    388             iret = NF90_PUT_VAR(ncid, scaling_id, this%mass_scaling, (/ k /) ) 
    389  
    390             iret = NF90_PUT_VAR(ncid, lonid, pt%lon, (/ k /) ) 
    391             iret = NF90_PUT_VAR(ncid, latid, pt%lat, (/ k /) ) 
    392             iret = NF90_PUT_VAR(ncid, xid, pt%xi, (/ k /) ) 
    393             iret = NF90_PUT_VAR(ncid, yid, pt%yj, (/ k /) ) 
    394             iret = NF90_PUT_VAR(ncid, uvelid, pt%uvel, (/ k /) ) 
    395             iret = NF90_PUT_VAR(ncid, vvelid, pt%vvel, (/ k /) ) 
    396             iret = NF90_PUT_VAR(ncid, massid, pt%mass, (/ k /) ) 
    397             iret = NF90_PUT_VAR(ncid, thicknessid, pt%thickness, (/ k /) ) 
    398             iret = NF90_PUT_VAR(ncid, widthid, pt%width, (/ k /) ) 
    399             iret = NF90_PUT_VAR(ncid, lengthid, pt%length, (/ k /) ) 
    400             iret = NF90_PUT_VAR(ncid, yearid, pt%year, (/ k /) ) 
    401             iret = NF90_PUT_VAR(ncid, dayid, pt%day, (/ k /) ) 
    402             iret = NF90_PUT_VAR(ncid, mass_of_bits_id, pt%mass_of_bits, (/ k /) ) 
    403             iret = NF90_PUT_VAR(ncid, heat_density_id, pt%heat_density, (/ k /) ) 
     387            jn=jn+1 
     388 
     389            nret = NF90_PUT_VAR(ncid, numberid, this%number, (/1,jn/), (/nkounts,1/) ) 
     390            nret = NF90_PUT_VAR(ncid, nscaling_id, this%mass_scaling, (/ jn /) ) 
     391 
     392            nret = NF90_PUT_VAR(ncid, nlonid, pt%lon, (/ jn /) ) 
     393            nret = NF90_PUT_VAR(ncid, nlatid, pt%lat, (/ jn /) ) 
     394            nret = NF90_PUT_VAR(ncid, nxid, pt%xi, (/ jn /) ) 
     395            nret = NF90_PUT_VAR(ncid, nyid, pt%yj, (/ jn /) ) 
     396            nret = NF90_PUT_VAR(ncid, nuvelid, pt%uvel, (/ jn /) ) 
     397            nret = NF90_PUT_VAR(ncid, nvvelid, pt%vvel, (/ jn /) ) 
     398            nret = NF90_PUT_VAR(ncid, nmassid, pt%mass, (/ jn /) ) 
     399            nret = NF90_PUT_VAR(ncid, nthicknessid, pt%thickness, (/ jn /) ) 
     400            nret = NF90_PUT_VAR(ncid, nwidthid, pt%width, (/ jn /) ) 
     401            nret = NF90_PUT_VAR(ncid, nlengthid, pt%length, (/ jn /) ) 
     402            nret = NF90_PUT_VAR(ncid, nyearid, pt%year, (/ jn /) ) 
     403            nret = NF90_PUT_VAR(ncid, ndayid, pt%day, (/ jn /) ) 
     404            nret = NF90_PUT_VAR(ncid, nmass_of_bits_id, pt%mass_of_bits, (/ jn /) ) 
     405            nret = NF90_PUT_VAR(ncid, nheat_density_id, pt%heat_density, (/ jn /) ) 
    404406 
    405407            this=>this%next 
     
    409411 
    410412      ! Finish up 
    411       iret = NF90_CLOSE(ncid) 
    412       IF (iret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed') 
     413      nret = NF90_CLOSE(ncid) 
     414      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed') 
    413415 
    414416   END SUBROUTINE icebergs_write_restart 
Note: See TracChangeset for help on using the changeset viewer.