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/IOM – NEMO

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

reduce global communications, see #2010

Location:
NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/IOM
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/IOM/in_out_manager.F90

    r9598 r10288  
    160160   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    161161   !! $Id$ 
    162    !! Software governed by the CeCILL licence     (./LICENSE) 
     162   !! Software governed by the CeCILL license (see ./LICENSE) 
    163163   !!===================================================================== 
    164164END MODULE in_out_manager 
  • NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/IOM/iom.F90

    r9802 r10288  
    4343   USE ioipsl, ONLY :  ju2ymds    ! for calendar 
    4444   USE crs             ! Grid coarsening 
     45#if defined key_top 
     46   USE trc, ONLY    :  profsed 
     47#endif 
    4548   USE lib_fortran  
    4649   USE diurnal_bulk, ONLY : ln_diurnal_only, ln_diurnal 
     
    8386      MODULE PROCEDURE iom_p0d, iom_p1d, iom_p2d, iom_p3d 
    8487   END INTERFACE iom_put 
    85     
    86    LOGICAL, PARAMETER ::   ltmppatch = .TRUE.     !: seb: patch before we remove periodicity 
    87    INTEGER            ::   nldi_save, nlei_save   !:      and close boundaries in output files 
    88    INTEGER            ::   nldj_save, nlej_save   !: 
    8988   
    9089   !!---------------------------------------------------------------------- 
    9190   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    9291   !! $Id$ 
    93    !! Software governed by the CeCILL licence (./LICENSE) 
     92   !! Software governed by the CeCILL license (see ./LICENSE) 
    9493   !!---------------------------------------------------------------------- 
    9594CONTAINS 
    9695 
    97    SUBROUTINE iom_init( cdname, fname )  
     96   SUBROUTINE iom_init( cdname, fname, ld_tmppatch )  
    9897      !!---------------------------------------------------------------------- 
    9998      !!                     ***  ROUTINE   *** 
     
    102101      !! 
    103102      !!---------------------------------------------------------------------- 
    104       CHARACTER(len=*), INTENT(in)  :: cdname 
     103      CHARACTER(len=*),           INTENT(in)  :: cdname 
    105104      CHARACTER(len=*), OPTIONAL, INTENT(in)  :: fname 
     105      LOGICAL         , OPTIONAL, INTENT(in)  :: ld_tmppatch 
    106106#if defined key_iomput 
    107107      ! 
     
    113113      ! 
    114114      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds 
     115      LOGICAL ::   ll_tmppatch = .TRUE.    !: seb: patch before we remove periodicity 
     116      INTEGER ::   nldi_save, nlei_save    !:      and close boundaries in output files 
     117      INTEGER ::   nldj_save, nlej_save    !: 
    115118      !!---------------------------------------------------------------------- 
    116119      ! 
    117120      ! seb: patch before we remove periodicity and close boundaries in output files 
    118       IF ( ltmppatch ) THEN 
     121      IF( PRESENT(ld_tmppatch) ) THEN   ;   ll_tmppatch = ld_tmppatch 
     122      ELSE                              ;   ll_tmppatch = .TRUE. 
     123      ENDIF 
     124      IF ( ll_tmppatch ) THEN 
    119125         nldi_save = nldi   ;   nlei_save = nlei 
    120126         nldj_save = nldj   ;   nlej_save = nlej 
     
    147153      ! 
    148154      IF( TRIM(cdname) == TRIM(cxios_context) ) THEN   
    149          CALL set_grid( "T", glamt, gphit, .FALSE. )  
    150          CALL set_grid( "U", glamu, gphiu, .FALSE. ) 
    151          CALL set_grid( "V", glamv, gphiv, .FALSE. ) 
    152          CALL set_grid( "W", glamt, gphit, .FALSE. ) 
     155         CALL set_grid( "T", glamt, gphit, .FALSE., .FALSE. )  
     156         CALL set_grid( "U", glamu, gphiu, .FALSE., .FALSE. ) 
     157         CALL set_grid( "V", glamv, gphiv, .FALSE., .FALSE. ) 
     158         CALL set_grid( "W", glamt, gphit, .FALSE., .FALSE. ) 
    153159         CALL set_grid_znl( gphit ) 
    154160         ! 
     
    168174         CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    169175         ! 
    170          CALL set_grid( "T", glamt_crs, gphit_crs, .FALSE. )  
    171          CALL set_grid( "U", glamu_crs, gphiu_crs, .FALSE. )  
    172          CALL set_grid( "V", glamv_crs, gphiv_crs, .FALSE. )  
    173          CALL set_grid( "W", glamt_crs, gphit_crs, .FALSE. )  
     176         CALL set_grid( "T", glamt_crs, gphit_crs, .FALSE., .FALSE. )  
     177         CALL set_grid( "U", glamu_crs, gphiu_crs, .FALSE., .FALSE. )  
     178         CALL set_grid( "V", glamv_crs, gphiv_crs, .FALSE., .FALSE. )  
     179         CALL set_grid( "W", glamt_crs, gphit_crs, .FALSE., .FALSE. )  
    174180         CALL set_grid_znl( gphit_crs ) 
    175181          ! 
     
    190196      ! vertical grid definition 
    191197      IF(.NOT.llrst_context) THEN 
    192           CALL iom_set_axis_attr( "deptht", paxis = gdept_1d ) 
    193           CALL iom_set_axis_attr( "depthu", paxis = gdept_1d ) 
    194           CALL iom_set_axis_attr( "depthv", paxis = gdept_1d ) 
    195           CALL iom_set_axis_attr( "depthw", paxis = gdepw_1d ) 
     198          CALL iom_set_axis_attr( "deptht",  paxis = gdept_1d ) 
     199          CALL iom_set_axis_attr( "depthu",  paxis = gdept_1d ) 
     200          CALL iom_set_axis_attr( "depthv",  paxis = gdept_1d ) 
     201          CALL iom_set_axis_attr( "depthw",  paxis = gdepw_1d ) 
    196202 
    197203          ! Add vertical grid bounds 
     
    216222          CALL iom_set_axis_attr( "nstrait", (/ (REAL(ji,wp), ji=1,4) /) ) 
    217223# endif 
     224#if defined key_top 
     225          CALL iom_set_axis_attr( "profsed", paxis = profsed ) 
     226#endif 
    218227          CALL iom_set_axis_attr( "icbcla", class_num ) 
    219228          CALL iom_set_axis_attr( "iax_20C", (/ REAL(20,wp) /) ) 
     
    224233      IF( TRIM(cdname) == TRIM(crxios_context) ) THEN 
    225234!set names of the fields in restart file IF using XIOS to read data 
    226           CALL iom_set_rst_context() 
     235          CALL iom_set_rst_context(.TRUE.) 
    227236          CALL iom_set_rst_vars(rst_rfields) 
    228237!set which fields are to be read from restart file 
     
    230239      ELSE IF( TRIM(cdname) == TRIM(cwxios_context) ) THEN 
    231240!set names of the fields in restart file IF using XIOS to write data 
    232           CALL iom_set_rst_context() 
     241          CALL iom_set_rst_context(.FALSE.) 
    233242          CALL iom_set_rst_vars(rst_wfields) 
    234243!set which fields are to be written to a restart file 
     
    246255      DEALLOCATE( zt_bnds, zw_bnds ) 
    247256      ! 
    248       IF ( ltmppatch ) THEN 
     257      IF ( ll_tmppatch ) THEN 
    249258         nldi = nldi_save   ;   nlei = nlei_save 
    250259         nldj = nldj_save   ;   nlej = nlej_save 
     
    568577   END SUBROUTINE iom_set_rstw_active 
    569578 
    570    SUBROUTINE iom_set_rst_context( )  
     579   SUBROUTINE iom_set_rst_context(ld_rstr)  
    571580     !!--------------------------------------------------------------------- 
    572581      !!                   ***  SUBROUTINE  iom_set_rst_context  *** 
     
    576585      !!                
    577586      !!--------------------------------------------------------------------- 
     587   LOGICAL, INTENT(IN)               :: ld_rstr 
     588!ld_rstr is true for restart context. There is no need to define grid for  
     589!restart read, because it's read from file 
    578590#if defined key_iomput 
    579591   TYPE(xios_domaingroup)            :: domaingroup_hdl  
     
    586598     CALL xios_get_handle("domain_definition",domaingroup_hdl)  
    587599     CALL xios_add_child(domaingroup_hdl, domain_hdl, "grid_N")  
    588      CALL set_grid("N", glamt, gphit, .TRUE.)  
     600     CALL set_grid("N", glamt, gphit, .TRUE., ld_rstr)  
    589601  
    590602     CALL xios_get_handle("axis_definition",axisgroup_hdl)  
     
    690702      ! do we read the overlap  
    691703      ! ugly patch SM+JMM+RB to overwrite global definition in some cases 
    692       !llnoov = (jpni * jpnj ) == jpnij .AND. .NOT. lk_agrif 
    693       !llnoov = .true. 
    694       llnoov = .NOT. lk_agrif 
     704      llnoov = (jpni * jpnj ) == jpnij .AND. .NOT. lk_agrif 
    695705      ! create the file name by added, if needed, TRIM(Agrif_CFixed()) and TRIM(clsuffix) 
    696706      ! ============= 
     
    17581768   !!---------------------------------------------------------------------- 
    17591769 
    1760    SUBROUTINE iom_set_domain_attr( cdid, ni_glo, nj_glo, ibegin, jbegin, ni, nj, zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj,   & 
     1770   SUBROUTINE iom_set_domain_attr( cdid, ni_glo, nj_glo, ibegin, jbegin, ni, nj,                                               & 
    17611771      &                                    data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask,     & 
    17621772      &                                    nvertex, bounds_lon, bounds_lat, area ) 
     
    17661776      INTEGER                 , OPTIONAL, INTENT(in) ::   ni_glo, nj_glo, ibegin, jbegin, ni, nj 
    17671777      INTEGER                 , OPTIONAL, INTENT(in) ::   data_dim, data_ibegin, data_ni, data_jbegin, data_nj 
    1768       INTEGER                 , OPTIONAL, INTENT(in) ::   zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj, nvertex 
     1778      INTEGER                 , OPTIONAL, INTENT(in) ::   nvertex 
    17691779      REAL(wp), DIMENSION(:)  , OPTIONAL, INTENT(in) ::   lonvalue, latvalue 
    17701780      REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(in) ::   bounds_lon, bounds_lat, area 
     
    17931803      !!---------------------------------------------------------------------- 
    17941804      !!---------------------------------------------------------------------- 
    1795       CHARACTER(LEN=*)          , INTENT(in) ::   cdid 
    1796       INTEGER         , OPTIONAL, INTENT(in) ::   ibegin, jbegin, ni, nj 
    1797       !!---------------------------------------------------------------------- 
    1798       IF( xios_is_valid_zoom_domain(cdid) )   CALL xios_set_zoom_domain_attr( cdid, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj ) 
     1805      CHARACTER(LEN=*), INTENT(in) ::   cdid 
     1806      INTEGER         , INTENT(in) ::   ibegin, jbegin, ni, nj 
     1807      ! 
     1808      TYPE(xios_gridgroup) :: gridgroup_hdl 
     1809      TYPE(xios_grid)      :: grid_hdl 
     1810      TYPE(xios_domain)    :: domain_hdl  
     1811      TYPE(xios_axis)      :: axis_hdl  
     1812      CHARACTER(LEN=64)    :: cldomrefid   ! domain_ref name 
     1813      CHARACTER(len=1)     :: cl1          ! last character of this name 
     1814      !!---------------------------------------------------------------------- 
     1815      ! 
     1816      IF( xios_is_valid_zoom_domain(cdid) ) THEN 
     1817         ! define the zoom_domain attributs 
     1818         CALL xios_set_zoom_domain_attr( cdid, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj ) 
     1819         ! define a new 2D grid with this new domain 
     1820         CALL xios_get_handle("grid_definition", gridgroup_hdl ) 
     1821         CALL xios_add_child(gridgroup_hdl, grid_hdl, TRIM(cdid)//'_2D' )   ! add a new 2D grid to grid_definition 
     1822         CALL xios_add_child(grid_hdl, domain_hdl, TRIM(cdid) )             ! add its domain 
     1823         ! define a new 3D grid with this new domain 
     1824         CALL xios_add_child(gridgroup_hdl, grid_hdl, TRIM(cdid)//'_3D' )   ! add a new 3D grid to grid_definition 
     1825         CALL xios_add_child(grid_hdl, domain_hdl, TRIM(cdid) )             ! add its domain 
     1826         ! vertical axis 
     1827         cl1 = cdid(LEN_TRIM(cdid):)                                        ! last letter of cdid 
     1828         cl1 = CHAR(ICHAR(cl1)+32)                                          ! from upper to lower case 
     1829         CALL xios_add_child(grid_hdl, axis_hdl, 'depth'//cl1)              ! add its axis 
     1830      ENDIF 
     1831      !       
    17991832   END SUBROUTINE iom_set_zoom_domain_attr 
    18001833 
     
    19091942 
    19101943 
    1911    SUBROUTINE set_grid( cdgrd, plon, plat, ldxios ) 
     1944   SUBROUTINE set_grid( cdgrd, plon, plat, ldxios, ldrxios ) 
    19121945      !!---------------------------------------------------------------------- 
    19131946      !!                     ***  ROUTINE set_grid  *** 
     
    19211954      INTEGER  :: ni, nj 
    19221955      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zmask 
    1923       LOGICAL, INTENT(IN) :: ldxios 
    1924       !!---------------------------------------------------------------------- 
    1925       ! 
    1926       ! seb: patch before we remove periodicity and close boundaries in output files 
    1927       IF ( ltmppatch ) THEN 
    1928          nldi_save = nldi   ;   nlei_save = nlei 
    1929          nldj_save = nldj   ;   nlej_save = nlej 
    1930          IF( nimpp           ==      1 ) nldi = 1 
    1931          IF( nimpp + jpi - 1 == jpiglo ) nlei = jpi 
    1932          IF( njmpp           ==      1 ) nldj = 1 
    1933          IF( njmpp + jpj - 1 == jpjglo ) nlej = jpj 
    1934       ENDIF 
     1956      LOGICAL, INTENT(IN) :: ldxios, ldrxios 
     1957      !!---------------------------------------------------------------------- 
    19351958      ! 
    19361959      ni = nlei-nldi+1 
     
    19391962      CALL iom_set_domain_attr("grid_"//cdgrd, ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-2, jbegin=njmpp+nldj-2, ni=ni, nj=nj) 
    19401963      CALL iom_set_domain_attr("grid_"//cdgrd, data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj) 
    1941       CALL iom_set_domain_attr("grid_"//cdgrd, lonvalue = RESHAPE(plon(nldi:nlei, nldj:nlej),(/ ni*nj /)),   & 
     1964!don't define lon and lat for restart reading context.  
     1965      IF ( .NOT.ldrxios ) & 
     1966         CALL iom_set_domain_attr("grid_"//cdgrd, lonvalue = RESHAPE(plon(nldi:nlei, nldj:nlej),(/ ni*nj /)),   & 
    19421967         &                                     latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
    19431968      ! 
     
    19551980      ENDIF 
    19561981      ! 
    1957       IF ( ltmppatch ) THEN 
    1958          nldi = nldi_save   ;   nlei = nlei_save 
    1959          nldj = nldj_save   ;   nlej = nlej_save 
    1960       ENDIF 
    1961       ! 
    19621982   END SUBROUTINE set_grid 
    19631983 
     
    19812001      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: z_rot       ! Lat/lon working array for rotation of cells 
    19822002      !!---------------------------------------------------------------------- 
    1983       ! 
    1984       ! seb: patch before we remove periodicity and close boundaries in output files 
    1985       IF ( ltmppatch ) THEN 
    1986          nldi_save = nldi   ;   nlei_save = nlei 
    1987          nldj_save = nldj   ;   nlej_save = nlej 
    1988          IF( nimpp           ==      1 ) nldi = 1 
    1989          IF( nimpp + jpi - 1 == jpiglo ) nlei = jpi 
    1990          IF( njmpp           ==      1 ) nldj = 1 
    1991          IF( njmpp + jpj - 1 == jpjglo ) nlej = jpj 
    1992       ENDIF 
    19932003      ! 
    19942004      ALLOCATE( z_bnds(4,jpi,jpj,2), z_fld(jpi,jpj), z_rot(4,2)  ) 
     
    20752085      DEALLOCATE( z_bnds, z_fld, z_rot )  
    20762086      ! 
    2077       IF ( ltmppatch ) THEN 
    2078          nldi = nldi_save   ;   nlei = nlei_save 
    2079          nldj = nldj_save   ;   nlej = nlej_save 
    2080       ENDIF 
    2081       ! 
    20822087   END SUBROUTINE set_grid_bounds 
    20832088 
     
    20952100      REAL(wp), DIMENSION(:), ALLOCATABLE  ::   zlon 
    20962101      !!---------------------------------------------------------------------- 
    2097       ! 
    2098       ! seb: patch before we remove periodicity and close boundaries in output files 
    2099       IF ( ltmppatch ) THEN 
    2100          nldi_save = nldi   ;   nlei_save = nlei 
    2101          nldj_save = nldj   ;   nlej_save = nlej 
    2102          IF( nimpp           ==      1 ) nldi = 1 
    2103          IF( nimpp + jpi - 1 == jpiglo ) nlei = jpi 
    2104          IF( njmpp           ==      1 ) nldj = 1 
    2105          IF( njmpp + jpj - 1 == jpjglo ) nlej = jpj 
    2106       ENDIF 
    21072102      ! 
    21082103      ni=nlei-nldi+1       ! define zonal mean domain (jpj*jpk) 
     
    21162111      CALL iom_set_domain_attr("gznl", lonvalue = zlon,   & 
    21172112         &                             latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
    2118       CALL iom_set_zoom_domain_attr ("ptr", ibegin=ix-1, jbegin=0, ni=1, nj=jpjglo) 
     2113      CALL iom_set_zoom_domain_attr("znl_T", ibegin=ix-1, jbegin=0, ni=1, nj=jpjglo) 
     2114      CALL iom_set_zoom_domain_attr("znl_W", ibegin=ix-1, jbegin=0, ni=1, nj=jpjglo) 
    21192115      ! 
    21202116      CALL iom_update_file_name('ptr') 
    2121       ! 
    2122       IF ( ltmppatch ) THEN 
    2123          nldi = nldi_save   ;   nlei = nlei_save 
    2124          nldj = nldj_save   ;   nlej = nlej_save 
    2125       ENDIF 
    21262117      ! 
    21272118   END SUBROUTINE set_grid_znl 
     
    21992190         ! Equatorial section (attributs: jbegin, ni, name_suffix) 
    22002191         CALL dom_ngb( 0., 0., ix, iy, cl1 ) 
    2201          CALL iom_set_zoom_domain_attr ('Eq'//cl1, jbegin=iy-1, ni=jpiglo) 
     2192         CALL iom_set_zoom_domain_attr('Eq'//cl1, ibegin=0, jbegin=iy-1, ni=jpiglo, nj=1 ) 
    22022193         CALL iom_get_file_attr   ('Eq'//cl1, name_suffix = clsuff             ) 
    22032194         CALL iom_set_file_attr   ('Eq'//cl1, name_suffix = TRIM(clsuff)//'_Eq') 
     
    22782269               ENDIF 
    22792270               clname = TRIM(ADJUSTL(clat))//TRIM(ADJUSTL(clon)) 
    2280                CALL iom_set_zoom_domain_attr  (TRIM(clname)//cl1, ibegin= ix-1, jbegin= iy-1) 
     2271               CALL iom_set_zoom_domain_attr(TRIM(clname)//cl1, ibegin= ix-1, jbegin= iy-1, ni=1, nj=1) 
    22812272 
    22822273               CALL iom_get_file_attr   (TRIM(clname)//cl1, name_suffix = clsuff                         ) 
  • NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/IOM/iom_def.F90

    r9598 r10288  
    8585   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    8686   !! $Id$ 
    87    !! Software governed by the CeCILL licence (./LICENSE) 
     87   !! Software governed by the CeCILL license (see ./LICENSE) 
    8888   !!====================================================================== 
    8989END MODULE iom_def 
  • NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/IOM/iom_nf90.F90

    r9598 r10288  
    4848   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    4949   !! $Id$ 
    50    !! Software governed by the CeCILL licence (./LICENSE) 
     50   !! Software governed by the CeCILL license (see ./LICENSE) 
    5151   !!---------------------------------------------------------------------- 
    5252CONTAINS 
  • NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/IOM/prtctl.F90

    r9667 r10288  
    3737   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    3838   !! $Id$  
    39    !! Software governed by the CeCILL licence     (./LICENSE) 
     39   !! Software governed by the CeCILL license (see ./LICENSE) 
    4040   !!---------------------------------------------------------------------- 
    4141CONTAINS 
  • NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/IOM/restart.F90

    r9654 r10288  
    4242   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    4343   !! $Id$ 
    44    !! Software governed by the CeCILL licence     (./LICENSE) 
     44   !! Software governed by the CeCILL license (see ./LICENSE) 
    4545   !!---------------------------------------------------------------------- 
    4646CONTAINS 
     
    118118                  clpname = TRIM(Agrif_CFixed())//"_"//clname    
    119119               ENDIF 
    120                CALL iom_init( cwxios_context, TRIM(clpath)//TRIM(clpname)) 
     120               CALL iom_init( cwxios_context, TRIM(clpath)//TRIM(clpname), .false. ) 
    121121               CALL xios_update_calendar(nitrst) 
    122122               CALL iom_swap(      cxios_context          ) 
     
    228228             IF( .NOT.lxios_set ) THEN 
    229229                 IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS' 
    230                  CALL iom_init( crxios_context ) 
     230                 CALL iom_init( crxios_context, ld_tmppatch = .false. ) 
    231231                 lxios_set = .TRUE. 
    232232             ENDIF 
    233233         ENDIF 
    234234         IF( TRIM(Agrif_CFixed()) /= '0' .AND. lrxios) THEN 
    235              CALL iom_init( crxios_context ) 
     235             CALL iom_init( crxios_context, ld_tmppatch = .false. ) 
    236236             IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS for AGRIF' 
    237237             lxios_set = .TRUE. 
Note: See TracChangeset for help on using the changeset viewer.