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 8045 – NEMO

Changeset 8045


Ignore:
Timestamp:
2017-05-19T11:21:44+02:00 (7 years ago)
Author:
marc
Message:

Broken up iron_chem_scav.F90 into sections

Location:
branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA/bio_medusa_init.F90

    r8023 r8045  
    4646      !! time (integer timestep) 
    4747      INTEGER, INTENT( in ) ::    kt 
    48  
    49 ! tmp - marc 
    50       write(numout,*) 'bbb1. kt=',kt 
    51       flush(numout) 
    52 ! 
    5348 
    5449      IF( ln_diatrc ) THEN 
     
    831826      !! lk_iomput 
    832827 
    833 ! tmp - marc 
    834       write(numout,*) 'bbb9. kt=',kt 
    835       flush(numout) 
    836 ! 
    837  
    838828   END SUBROUTINE bio_medusa_init 
    839829 
  • branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA/iron_chem_scav.F90

    r7978 r8045  
    3737                                   mbathy, tmask 
    3838      USE par_kind,          ONLY: wp 
    39       USE par_oce,           ONLY: jpim1, jpjm1 
     39      USE par_oce,           ONLY: jpi, jpim1, jpj, jpjm1 
    4040      USE sms_medusa,        ONLY: i0500, jiron, xfe_sed, xfe_sol,        & 
    4141                                   xk_FeL, xk_sc_Fe, xLgT,                & 
     
    5353      !! iron cycle; includes parameters for Parekh et al. (2005) iron scheme 
    5454      !! state variables for iron-ligand system 
    55       REAL(wp) ::    xLgF, xFeT, xFeF, xFeL 
     55      REAL(wp), DIMENSION(jpi,jpj) :: xFeT, xFeF, xFeL 
     56      REAL(wp) :: xLgF 
    5657      !! iron-ligand parameters 
    57       REAL(wp) ::    xb_coef_tmp, xb2M4ac 
     58      REAL(wp) :: xb_coef_tmp, xb2M4ac 
    5859      !! max Fe' parameters 
    59       REAL(wp) ::    xmaxFeF,fdeltaFe 
     60      REAL(wp) :: xmaxFeF,fdeltaFe 
    6061      !! 
    6162      !! local parameters for Moore et al. (2004) alternative scavenging  
    6263      !! scheme 
    63       REAL(wp) ::    fbase_scav,fscal_sink,fscal_part,fscal_scav 
     64      REAL(wp) :: fbase_scav,fscal_sink,fscal_part,fscal_scav 
    6465      !! 
    6566      !! local parameters for Moore et al. (2008) alternative scavenging  
    6667      !! scheme 
    67       REAL(wp) ::    fscal_csink,fscal_sisink,fscal_casink 
     68      REAL(wp) :: fscal_csink,fscal_sisink,fscal_casink 
    6869      !! 
    6970      !! local parameters for Galbraith et al. (2010) alternative  
    7071      !! scavenging scheme. 
    7172      !! organic portion of scavenging 
    72       REAL(wp) ::    xCscav1, xCscav2, xk_org, xORGscav 
     73      REAL(wp) :: xCscav1, xCscav2, xk_org, xORGscav 
    7374      !! inorganic portion of scavenging 
    74       REAL(wp) ::    xk_inorg, xINORGscav 
     75      REAL(wp) :: xk_inorg, xINORGscav 
    7576 
    7677      INTEGER :: ji, jj 
    77  
    78 ! I'D LIKE TO PULL THE IF (jiron) statements outside the DO loops - marc 
    7978 
    8079      !!------------------------------------------------------------------ 
     
    9190               !! 
    9291               !! total iron concentration (mmol Fe / m3 -> umol Fe / m3) 
    93                xFeT        = zfer(ji,jj) * 1.e3 
     92               xFeT(ji,jj) = zfer(ji,jj) * 1.e3 
    9493               !! 
    9594               !! calculate fractionation (based on Diat-HadOCC; in turn  
    9695               !! based on Parekh et al., 2004) 
    97                xb_coef_tmp = xk_FeL * (xLgT - xFeT) - 1.0 
     96               xb_coef_tmp = xk_FeL * (xLgT - xFeT(ji,jj)) - 1.0 
    9897               xb2M4ac     = max(((xb_coef_tmp * xb_coef_tmp) +              & 
    9998                                  (4.0 * xk_FeL * xLgT)), 0.0) 
     
    103102               !! 
    104103               !! ligand-bound iron concentration 
    105                xFeL        = xLgT - xLgF 
     104               xFeL(ji,jj) = xLgT - xLgF 
    106105               !! 
    107106               !! "free" iron concentration (and convert to mmol Fe / m3) 
    108                xFeF        = (xFeT - xFeL) * 1.e-3 
    109                xFree(ji,jj)= xFeF / (zfer(ji,jj) + tiny(zfer(ji,jj))) 
    110                !! 
    111                !! scavenging of iron (multiple schemes); I'm only really  
    112                !! happy with the first one at the moment - the others  
    113                !! involve assumptions (sometimes guessed at by me) that  
    114                !! are potentially questionable 
    115                !! 
    116                if (jiron.eq.1) then 
    117                   !!------------------------------------------------------ 
    118                   !! Scheme 1: Dutkiewicz et al. (2005) 
    119                   !! This scheme includes a single scavenging term based  
    120                   !! solely on a fixed rate and the availablility of  
    121                   !! "free" iron 
    122                   !!------------------------------------------------------ 
     107               xFeF(ji,jj) = (xFeT(ji,jj) - xFeL(ji,jj)) * 1.e-3 
     108               xFree(ji,jj)= xFeF(ji,jj) / (zfer(ji,jj) + tiny(zfer(ji,jj))) 
     109            ENDIF 
     110         ENDDO 
     111      ENDDO 
     112 
     113 
     114      !! 
     115      !! scavenging of iron (multiple schemes); I'm only really  
     116      !! happy with the first one at the moment - the others  
     117      !! involve assumptions (sometimes guessed at by me) that  
     118      !! are potentially questionable 
     119      !! 
     120      if (jiron.eq.1) then 
     121         !!------------------------------------------------------ 
     122         !! Scheme 1: Dutkiewicz et al. (2005) 
     123         !! This scheme includes a single scavenging term based  
     124         !! solely on a fixed rate and the availablility of  
     125         !! "free" iron 
     126         !!------------------------------------------------------ 
     127         DO jj = 2,jpjm1 
     128            DO ji = 2,jpim1 
     129               IF (tmask(ji,jj,jk) == 1) THEN 
    123130                  !! = mmol/m3/d 
    124                   ffescav(ji,jj)     = xk_sc_Fe * xFeF 
     131                  ffescav(ji,jj)     = xk_sc_Fe * xFeF(ji,jj) 
    125132                  !! 
    126133                  !!------------------------------------------------------ 
     
    135142                  !! constrained to a maximum of ... 
    136143                  !! 
    137                   !!    xFeL + min(xFeF, 0.3 umol/m3) = 1.0 + 0.3  
     144                  !!    xFeL(ji,jj) + min(xFeF(ji,jj), 0.3 umol/m3) = 1.0 + 0.3  
    138145                  !!                                  = 1.3 umol / m3 
    139146                  !!  
     
    148155                  !! 
    149156                  !! = umol/m3 
    150                   xmaxFeF     = min((xFeF * 1.e3), 0.3) 
     157                  xmaxFeF     = min((xFeF(ji,jj) * 1.e3), 0.3) 
    151158                  !! 
    152159                  !! Here, the difference between current total Fe and  
     
    155162                  !! 
    156163                  !! = mmol/m3 
    157                   fdeltaFe    = (xFeT - (xFeL + xmaxFeF)) * 1.e-3 
     164                  fdeltaFe    = (xFeT(ji,jj) - (xFeL(ji,jj) + xmaxFeF)) * 1.e-3 
    158165                  !! 
    159166                  !! This assumes that the "excess" iron is dissipated  
     
    182189                  !! a paper though! 
    183190                  !! 
    184                   if ((fsdepw(ji,jj,jk).gt.1000.) .and. (xFeT.lt.0.5)) then 
     191                  if ((fsdepw(ji,jj,jk).gt.1000.) .and.                       & 
     192                       (xFeT(ji,jj).lt.0.5)) then 
    185193                     ffescav(ji,jj) = 0. 
    186194                  endif 
    187195# endif 
    188                   !! 
    189                elseif (jiron.eq.2) then 
    190                   !!------------------------------------------------------ 
    191                   !! Scheme 2: Moore et al. (2004) 
    192                   !! This scheme includes a single scavenging term that  
    193                   !! accounts for both suspended and sinking particles in  
    194                   !! the water column; this term scavenges total iron rather  
    195                   !! than "free" iron 
    196                   !!------------------------------------------------------ 
     196               ENDIF 
     197            ENDDO 
     198         ENDDO 
     199      elseif (jiron.eq.2) then 
     200         !!------------------------------------------------------ 
     201         !! Scheme 2: Moore et al. (2004) 
     202         !! This scheme includes a single scavenging term that  
     203         !! accounts for both suspended and sinking particles in  
     204         !! the water column; this term scavenges total iron rather  
     205         !! than "free" iron 
     206         !!------------------------------------------------------ 
     207         DO jj = 2,jpjm1 
     208            DO ji = 2,jpim1 
     209               IF (tmask(ji,jj,jk) == 1) THEN 
    197210                  !! 
    198211                  !! total iron concentration (mmol Fe / m3 -> umol Fe / m3) 
    199                   xFeT        = zfer(ji,jj) * 1.e3 
     212                  xFeT(ji,jj) = zfer(ji,jj) * 1.e3 
    200213                  !! 
    201214                  !! this has a base scavenging rate (12% / y) which is  
     
    253266                  !! regions; less alone in intermediate iron regions) 
    254267                  !! 
    255                   if (xFeT.lt.0.4) then 
     268                  if (xFeT(ji,jj).lt.0.4) then 
    256269                     !! 
    257270                     !! low iron region 
    258271                     !! 
    259                      fscal_scav = fscal_scav * (xFeT / 0.4) 
    260                      !! 
    261                   elseif (xFeT.gt.0.6) then 
     272                     fscal_scav = fscal_scav * (xFeT(ji,jj) / 0.4) 
     273                     !! 
     274                  elseif (xFeT(ji,jj).gt.0.6) then 
    262275                     !! 
    263276                     !! high iron region 
    264277                     !! 
    265                      fscal_scav = fscal_scav + ((xFeT / 0.6) * (6.0 / 1.4)) 
     278                     fscal_scav = fscal_scav + ((xFeT(ji,jj) / 0.6) *        & 
     279                                                (6.0 / 1.4)) 
    266280                     !! 
    267281                  else 
     
    275289                  ffescav(ji,jj) = fscal_scav * zfer(ji,jj) 
    276290                  !! 
    277                elseif (jiron.eq.3) then 
    278                   !!------------------------------------------------------ 
    279                   !! Scheme 3: Moore et al. (2008) 
    280                   !! This scheme includes a single scavenging term that  
    281                   !! accounts for sinking particles in the water column,  
    282                   !! and includes organic C, biogenic opal, calcium  
    283                   !! carbonate and dust in this (though the latter is  
    284                   !! ignored here until I work out what units the incoming 
    285                   !! "dust" flux is in); this term scavenges total iron  
    286                   !! rather than "free" iron 
    287                   !!------------------------------------------------------ 
     291               ENDIF 
     292            ENDDO 
     293         ENDDO 
     294      elseif (jiron.eq.3) then 
     295         !!------------------------------------------------------ 
     296         !! Scheme 3: Moore et al. (2008) 
     297         !! This scheme includes a single scavenging term that  
     298         !! accounts for sinking particles in the water column,  
     299         !! and includes organic C, biogenic opal, calcium  
     300         !! carbonate and dust in this (though the latter is  
     301         !! ignored here until I work out what units the incoming 
     302         !! "dust" flux is in); this term scavenges total iron  
     303         !! rather than "free" iron 
     304         !!------------------------------------------------------ 
     305         DO jj = 2,jpjm1 
     306            DO ji = 2,jpim1 
     307               IF (tmask(ji,jj,jk) == 1) THEN 
    288308                  !! 
    289309                  !! total iron concentration (mmol Fe / m3 -> umol Fe / m3) 
    290                   xFeT        = zfer(ji,jj) * 1.e3 
     310                  xFeT(ji,jj) = zfer(ji,jj) * 1.e3 
    291311                  !! 
    292312                  !! this has a base scavenging rate which is modified by  
     
    312332                  !! milli -> nano; mol -> gram; /m2 -> /cm2; /d -> /s 
    313333                  !! ng C  / cm2 / s 
    314                   fscal_csink  = (ffastc(ji,jj)  * 1.e6 * xmassc  *           & 
     334                  fscal_csink  = (ffastc(ji,jj)  * 1.e6 * xmassc  *          & 
    315335                                  1.e-4 / 86400.) 
    316336                  !! ng Si / cm2 / s 
    317                   fscal_sisink = (ffastsi(ji,jj) * 1.e6 * xmasssi *           & 
     337                  fscal_sisink = (ffastsi(ji,jj) * 1.e6 * xmasssi *          & 
    318338                                  1.e-4 / 86400.) 
    319339                  !! ng Ca / cm2 / s 
    320                   fscal_casink = (ffastca(ji,jj) * 1.e6 * xmassca *           & 
     340                  fscal_casink = (ffastca(ji,jj) * 1.e6 * xmassca *          & 
    321341                                  1.e-4 / 86400.) 
    322342                  !!  
     
    341361                  !! regions; less alone in intermediate iron regions) 
    342362                  !! 
    343                   if (xFeT.lt.0.5) then 
     363                  if (xFeT(ji,jj).lt.0.5) then 
    344364                     !! 
    345365                     !! low iron region (0.5 instead of the 0.4 in Moore  
    346366                     !! et al., 2004) 
    347367                     !! 
    348                      fscal_scav = fscal_scav * (xFeT / 0.5) 
    349                      !! 
    350                   elseif (xFeT.gt.0.6) then 
     368                     fscal_scav = fscal_scav * (xFeT(ji,jj) / 0.5) 
     369                     !! 
     370                  elseif (xFeT(ji,jj).gt.0.6) then 
    351371                     !! 
    352372                     !! high iron region (functional form different in  
    353373                     !! Moore et al., 2004) 
    354374                     !! 
    355                      fscal_scav = fscal_scav + ((xFeT - 0.6) * 0.00904) 
     375                     fscal_scav = fscal_scav + ((xFeT(ji,jj) - 0.6) * 0.00904) 
    356376                     !! 
    357377                  else 
     
    364384                  !! 
    365385                  ffescav(ji,jj) = fscal_scav * zfer(ji,jj) 
    366                   !! 
    367                elseif (jiron.eq.4) then 
    368                   !!------------------------------------------------------ 
    369                   !! Scheme 4: Galbraith et al. (2010) 
    370                   !! This scheme includes two scavenging terms, one for  
    371                   !! organic, particle-based scavenging, and another for  
    372                   !! inorganic scavenging; both terms scavenge "free" iron  
    373                   !! only 
    374                   !!------------------------------------------------------ 
     386               ENDIF 
     387            ENDDO 
     388         ENDDO 
     389      elseif (jiron.eq.4) then 
     390         !!------------------------------------------------------ 
     391         !! Scheme 4: Galbraith et al. (2010) 
     392         !! This scheme includes two scavenging terms, one for  
     393         !! organic, particle-based scavenging, and another for  
     394         !! inorganic scavenging; both terms scavenge "free" iron  
     395         !! only 
     396         !!------------------------------------------------------ 
     397         DO jj = 2,jpjm1 
     398            DO ji = 2,jpim1 
     399               IF (tmask(ji,jj,jk) == 1) THEN 
    375400                  !! 
    376401                  !! Galbraith et al. (2010) present a more straightforward  
     
    380405                  !! this assumes a sinking rate of 100 m / d (Moore &  
    381406                  !! Braucher, 2008), 
    382                   xCscav1     = (ffastc(ji,jj) * xmassc) / 100. ! = mg C / m3 
     407                  xCscav1    = (ffastc(ji,jj) * xmassc) / 100. ! = mg C / m3 
    383408                  !!  
    384409                  !! scale by Honeyman et al. (1981) exponent coefficient 
    385410                  !! multiply by 1.e-3 to express C flux in g C rather than  
    386411                  !! mg C 
    387                   xCscav2     = (xCscav1 * 1.e-3)**0.58 
     412                  xCscav2    = (xCscav1 * 1.e-3)**0.58 
    388413                  !! 
    389414                  !! multiply by Galbraith et al. (2010) scavenging rate 
    390                   xk_org      = 0.5 ! ((g C m/3)^-1) / d 
    391                   xORGscav    = xk_org * xCscav2 * xFeF 
     415                  xk_org     = 0.5 ! ((g C m/3)^-1) / d 
     416                  xORGscav   = xk_org * xCscav2 * xFeF(ji,jj) 
    392417                  !! 
    393418                  !! Galbraith et al. (2010) also include an inorganic bit ... 
     
    396421                  !! availability of "free" iron 
    397422                  !! 
    398                   !! k_inorg  = 1000 d**-1 nmol Fe**-0.5 kg**-0.5 
     423                  !! k_inorg = 1000 d**-1 nmol Fe**-0.5 kg**-0.5 
    399424                  !! 
    400425                  !! to implement this here, scale xFeF by 1026 to put in  
    401426                  !! units of umol/m3 which approximately equal nmol/kg 
    402427                  !! 
    403                   xk_inorg    = 1000. ! ((nmol Fe / kg)^1.5) 
    404                   xINORGscav  = (xk_inorg * (xFeF * 1026.)**1.5) * 1.e-3 
     428                  xk_inorg   = 1000. ! ((nmol Fe / kg)^1.5) 
     429                  xINORGscav = (xk_inorg * (xFeF(ji,jj) * 1026.)**1.5) * 1.e-3 
    405430                  !! 
    406431                  !! sum these two terms together 
    407                   ffescav(ji,jj)     = xORGscav + xINORGscav 
    408                else 
    409                   !!------------------------------------------------------ 
    410                   !! No Scheme: you coward! 
    411                   !! This scheme puts its head in the sand and eskews any  
    412                   !! decision about how iron is removed from the ocean;  
    413                   !! prepare to get deluged in iron you fool! 
    414                   !!------------------------------------------------------ 
    415                   ffescav(ji,jj)     = 0. 
    416                endif 
    417  
    418                !!--------------------------------------------------------- 
    419                !! Other iron cycle processes 
    420                !!--------------------------------------------------------- 
    421                !! 
    422                !! aeolian iron deposition 
    423                if (jk.eq.1) then 
    424                   !! zirondep   is in mmol-Fe / m2 / day 
    425                   !! ffetop(ji,jj)     is in mmol-dissolved-Fe / m3 / day 
     432                  ffescav(ji,jj) = xORGscav + xINORGscav 
     433               ENDIF 
     434            ENDDO 
     435         ENDDO 
     436      else 
     437         !!------------------------------------------------------ 
     438         !! No Scheme: you coward! 
     439         !! This scheme puts its head in the sand and eskews any  
     440         !! decision about how iron is removed from the ocean;  
     441         !! prepare to get deluged in iron you fool! 
     442         !!------------------------------------------------------ 
     443         DO jj = 2,jpjm1 
     444            DO ji = 2,jpim1 
     445               IF (tmask(ji,jj,jk) == 1) THEN 
     446                  ffescav(ji,jj) = 0. 
     447               ENDIF 
     448            ENDDO 
     449         ENDDO 
     450      endif 
     451 
     452      !!--------------------------------------------------------- 
     453      !! Other iron cycle processes 
     454      !!--------------------------------------------------------- 
     455      !! 
     456      !! aeolian iron deposition 
     457      !! zirondep      is in mmol-Fe / m2 / day 
     458      !! ffetop(ji,jj) is in mmol-dissolved-Fe / m3 / day 
     459      if (jk == 1) then 
     460         DO jj = 2,jpjm1 
     461            DO ji = 2,jpim1 
     462               IF (tmask(ji,jj,jk) == 1) THEN 
    426463                  ffetop(ji,jj)  = zirondep(ji,jj) * xfe_sol / fse3t(ji,jj,jk)  
    427                else 
     464               ENDIF 
     465            ENDDO 
     466         ENDDO 
     467      else 
     468         DO jj = 2,jpjm1 
     469            DO ji = 2,jpim1 
     470               IF (tmask(ji,jj,jk) == 1) THEN 
    428471                  ffetop(ji,jj)  = 0.0 
    429                endif 
    430                !! 
    431                !! seafloor iron addition 
     472                ENDIF 
     473            ENDDO 
     474         ENDDO 
     475      endif 
     476      !! 
     477      !! seafloor iron addition 
     478      DO jj = 2,jpjm1 
     479         DO ji = 2,jpim1 
     480            IF (tmask(ji,jj,jk) == 1) THEN 
    432481               !! AXY (10/07/12): amended to only apply sedimentary flux up  
    433482               !! to ~500 m down 
     
    444493                  ffebot(ji,jj)  = 0.0 
    445494               endif 
    446  
    447                !! AXY (16/12/09): remove iron addition/removal processes 
    448                !! For the purposes of the quarter degree run, the iron  
    449                !! cycle is being pegged to the initial condition supplied  
    450                !! by Mick Follows via restoration with a 30 day period; 
    451                !! iron addition at the seafloor is still permitted with  
    452                !! the idea that this extra iron will be removed by the  
    453                !! restoration away from the source 
    454                !! ffescav(ji,jj) = 0.0 
    455                !! ffetop(ji,jj)  = 0.0 
    456                !! ffebot(ji,jj)  = 0.0 
     495            ENDIF 
     496         ENDDO 
     497      ENDDO 
     498 
     499      !! AXY (16/12/09): remove iron addition/removal processes 
     500      !! For the purposes of the quarter degree run, the iron  
     501      !! cycle is being pegged to the initial condition supplied  
     502      !! by Mick Follows via restoration with a 30 day period; 
     503      !! iron addition at the seafloor is still permitted with  
     504      !! the idea that this extra iron will be removed by the  
     505      !! restoration away from the source 
     506      !! ffescav(ji,jj) = 0.0 
     507      !! ffetop(ji,jj)  = 0.0 
     508      !! ffebot(ji,jj)  = 0.0 
    457509 
    458510# if defined key_debug_medusa 
    459                !! report miscellaneous calculations 
    460                if (idf.eq.1.AND.idfval.eq.1) then 
     511      !! report miscellaneous calculations 
     512      !! report miscellaneous calculations 
     513      if (idf.eq.1.AND.idfval.eq.1) then 
     514         DO jj = 2,jpjm1 
     515            DO ji = 2,jpim1 
     516               IF (tmask(ji,jj,jk) == 1) THEN 
    461517                  IF (lwp) write (numout,*) '------------------------------' 
    462518                  IF (lwp) write (numout,*) 'xfe_sol  = ', xfe_sol 
     
    466522                  IF (lwp) write (numout,*) 'xFree(',jk,')   = ', xFree(ji,jj) 
    467523                  IF (lwp) write (numout,*) 'ffescav(',jk,') = ', ffescav(ji,jj) 
    468                endif 
     524               ENDIF 
     525            ENDDO 
     526         ENDDO 
     527      endif 
    469528# endif 
    470             ENDIF 
    471          ENDDO 
    472       ENDDO 
    473529 
    474530   END SUBROUTINE iron_chem_scav 
  • branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcsms_medusa.F90

    r7912 r8045  
    8282      CALL flush(numout) 
    8383# else 
    84 ! tmp - marc 
    85       write(numout,*) 'bbb25. before call to trc_bio_medusa' 
    86       flush(numout) 
    87 ! 
    8884      CALL trc_bio_medusa( kt ) ! biological model 
    8985#  if defined key_debug_medusa 
    9086      IF(lwp) WRITE(numout,*) ' MEDUSA done trc_bio_medusa' 
    9187      CALL flush(numout) 
    92 ! tmp - marc 
    93       write(numout,*) 'bbb26. after call to trc_bio_medusa' 
    94       flush(numout) 
    95 ! 
    9688#  endif 
    9789       
Note: See TracChangeset for help on using the changeset viewer.