Changeset 2440


Ignore:
Timestamp:
Feb 9, 2016, 3:45:31 PM (8 years ago)
Author:
lguez
Message:

For read_climoz = 1 or 2, replaced first order conservative regridding
of ozone by second order conservative regridding, with Van Leer
slope-limiting. The replacement is done for both latitude and pressure
regridding. The replacement is beneficial if the resolution of the
input data is coarser than the resolution of LMDZ. If the resolution
of the input data is finer, then the replacement is neutral, it does
not change much.

Location:
LMDZ5/trunk/libf
Files:
2 added
5 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/obsolete/LIST.txt

    r2321 r2440  
    66phylmd/mkstat.F90             2320
    77phylmd/inistats.F90           2320
     8misc/regr1_step_av_m.F90      2439
  • LMDZ5/trunk/libf/phylmd/regr_lat_time_climoz_m.F90

    r2346 r2440  
    6767
    6868    use mod_grid_phy_lmdz, ONLY : nbp_lat
    69     use regr1_step_av_m, only: regr1_step_av
     69    use regr1_conserv_m, only: regr1_conserv
    7070    use regr3_lint_m, only: regr3_lint
    7171    use netcdf95, only: handle_err, nf95_close, nf95_get_att, nf95_gw_var, &
     
    7676    use regular_lonlat_mod, only : boundslat_reg, south
    7777    use nrtype, only: pi
     78    use slopes_m, only: slopes
    7879
    7980    integer, intent(in):: read_climoz ! read ozone climatology
     
    9293    ! (of input data, converted to rad, sorted in strictly ascending order)
    9394
    94     real, allocatable:: lat_in_edg(:)
    95     ! (edges of latitude intervals for input data, in rad, in strictly
     95    real, allocatable:: sin_lat_in_edg(:)
     96    ! (sine of edges of latitude intervals for input data, in rad, in strictly
    9697    ! ascending order)
    9798
     
    115116
    116117    real, allocatable:: o3_regr_lat(:, :, :, :)
    117     ! (jjm + 1, n_plev, 0:13, read_climoz)
     118    ! (nbp_lat, n_plev, 0:13, read_climoz)
    118119    ! mean of "o3_in" over a latitude interval of LMDZ
    119120    ! First dimension is latitude interval.
    120121    ! The latitude interval for "o3_regr_lat(j,:, :, :)" contains "rlatu(j)".
    121     ! If "j" is between 2 and "jjm" then the interval is:
     122    ! If "j" is between 2 and "nbp_lat - 1" then the interval is:
    122123    ! [rlatv(j), rlatv(j-1)]
    123     ! If "j" is 1 or "jjm + 1" then the interval is:
     124    ! If "j" is 1 or "nbp_lat" then the interval is:
    124125    ! [rlatv(1), pi / 2]
    125126    ! or:
    126     ! [- pi / 2, rlatv(jjm)]
     127    ! [- pi / 2, rlatv(nbp_lat - 1)]
    127128    ! respectively.
    128129    ! "o3_regr_lat(:, k, :, :)" is for pressure level "plev(k)".
     
    132133
    133134    real, allocatable:: o3_out(:, :, :, :)
    134     ! (jjm + 1, n_plev, 360, read_climoz)
     135    ! (nbp_lat, n_plev, 360, read_climoz)
    135136    ! regridded ozone climatology
    136137    ! "o3_out(j, k, l, :)" is at latitude "rlatu(j)", pressure
     
    175176    latitude = latitude / 180. * pi
    176177    n_lat = size(latitude)
    177     ! We need to supply the latitudes to "regr1_step_av" in
     178    ! We need to supply the latitudes to "regr1_conserv" in
    178179    ! ascending order, so invert order if necessary:
    179180    desc_lat = latitude(1) > latitude(n_lat)
     
    181182
    182183    ! Compute edges of latitude intervals:
    183     allocate(lat_in_edg(n_lat + 1))
    184     lat_in_edg(1) = - pi / 2
    185     forall (j = 2:n_lat) lat_in_edg(j) = (latitude(j - 1) + latitude(j)) / 2
    186     lat_in_edg(n_lat + 1) = pi / 2
     184    allocate(sin_lat_in_edg(n_lat + 1))
     185    sin_lat_in_edg(1) = - 1.
     186    forall (j = 2:n_lat) sin_lat_in_edg(j) = sin((latitude(j - 1) &
     187         + latitude(j)) / 2.)
     188    sin_lat_in_edg(n_lat + 1) = 1.
    187189    deallocate(latitude) ! pointer
    188190
     
    292294       print *, &
    293295            "Found 12 months in ozone climatologies, assuming periodicity..."
    294        o3_regr_lat(nbp_lat:1:-1, :, 1:12, :) = regr1_step_av(o3_in, &
    295             xs=sin(lat_in_edg), xt=sin((/- pi / 2, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
     296       call regr1_conserv(o3_in, xs = sin_lat_in_edg, &
     297            xt = (/- 1., sin(boundslat_reg(nbp_lat - 1:1:- 1, south)), 1./), &
     298            vt = o3_regr_lat(nbp_lat:1:- 1, :, 1:12, :), &
     299            slope = slopes(o3_in, sin_lat_in_edg))
    296300       ! (invert order of indices in "o3_regr_lat" because "rlatu" is
    297301       ! in descending order)
     
    303307    else
    304308       print *, "Using 14 months in ozone climatologies..."
    305        o3_regr_lat(nbp_lat:1:-1, :, :, :) = regr1_step_av(o3_in, &
    306             xs=sin(lat_in_edg), xt=sin((/- pi / 2, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
     309       call regr1_conserv(o3_in, xs = sin_lat_in_edg, &
     310            xt = (/- 1., sin(boundslat_reg(nbp_lat - 1:1:- 1, south)), 1./), &
     311            vt = o3_regr_lat(nbp_lat:1:- 1, :, :, :), &
     312            slope = slopes(o3_in, sin_lat_in_edg))
    307313       ! (invert order of indices in "o3_regr_lat" because "rlatu" is
    308314       ! in descending order)
  • LMDZ5/trunk/libf/phylmd/regr_lat_time_coefoz_m.F90

    r2346 r2440  
    4141
    4242    use mod_grid_phy_lmdz, ONLY : nbp_lat
    43     use regr1_step_av_m, only: regr1_step_av
     43    use regr1_conserv_m, only: regr1_conserv
    4444    use regr3_lint_m, only: regr3_lint
    4545    use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, handle_err, &
     
    162162    latitude = latitude / 180. * pi
    163163    n_lat = size(latitude)
    164     ! We need to supply the latitudes to "regr1_step_av" in
     164    ! We need to supply the latitudes to "regr1_conserv" in
    165165    ! ascending order, so invert order if necessary:
    166166    desc_lat = latitude(1) > latitude(n_lat)
     
    209209       ! We average with respect to sine of latitude, which is
    210210       ! equivalent to weighting by cosine of latitude:
    211        v_regr_lat(nbp_lat:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &
    212             xs=sin(lat_in_edg), xt=sin((/- pi / 2, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
     211       call regr1_conserv(o3_par_in, xs = sin(lat_in_edg), &
     212            xt = (/-1., sin((/boundslat_reg(nbp_lat-1:1:-1,south)/)), 1./), &
     213            vt = v_regr_lat(nbp_lat:1:-1, :, 1:12))
    213214       ! (invert order of indices in "v_regr_lat" because "rlatu" is
    214215       ! in descending order)
  • LMDZ5/trunk/libf/phylmd/regr_pr_av_m.F90

    r2346 r2440  
    2626
    2727    ! The target vertical LMDZ grid is the grid of layer boundaries.
    28     ! Regridding in pressure is done by averaging a step function of pressure.
     28    ! Regridding in pressure is conservative, second order.
    2929
    3030    ! All the fields are regridded as a single multi-dimensional array
     
    3838    use assert_m, only: assert
    3939    use assert_eq_m, only: assert_eq
    40     use regr1_step_av_m, only: regr1_step_av
     40    use regr1_conserv_m, only: regr1_conserv
     41    use slopes_m, only: slopes
    4142    use mod_phys_lmdz_mpi_data, only: is_mpi_root
    4243    use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev
     
    8384    !--------------------------------------------
    8485
    85     call assert(size(v3, 1) == klon, size(v3, 2) == nbp_lev, "regr_pr_av v3 klon")
     86    call assert(size(v3, 1) == klon, size(v3, 2) == nbp_lev, &
     87         "regr_pr_av v3 klon")
    8688    n_var = assert_eq(size(name), size(v3, 3), "regr_pr_av v3 n_var")
    8789    call assert(shape(paprs) == (/klon, nbp_lev+1/), "regr_pr_av paprs")
     
    112114    ! Regrid in pressure at each horizontal position:
    113115    do i = 1, klon
    114        v3(i, nbp_lev:1:-1, :) = regr1_step_av(v2(i, :, :), press_in_edg, &
    115             paprs(i, nbp_lev+1:1:-1))
     116       call regr1_conserv(v2(i, :, :), press_in_edg, &
     117            paprs(i, nbp_lev + 1:1:-1), v3(i, nbp_lev:1:-1, :), &
     118            slopes(v2(i, :, :), press_in_edg))
    116119       ! (invert order of indices because "paprs" is in descending order)
    117120    end do
  • LMDZ5/trunk/libf/phylmd/regr_pr_o3_m.F90

    r2346 r2440  
    2828    use netcdf, only:  nf90_nowrite, nf90_get_var
    2929    use assert_m, only: assert
    30     use regr1_step_av_m, only: regr1_step_av
     30    use regr1_conserv_m, only: regr1_conserv
    3131    use press_coefoz_m, only: press_in_edg
    3232    use time_phylmdz_mod, only: day_ref
     
    7575    ! Poles:
    7676    do j = 1, nbp_lat, nbp_lat-1
    77        o3_mob_regr(1, j, nbp_lev:1:-1) &
    78             = regr1_step_av(r_mob(j, :), press_in_edg, p3d(1, j, nbp_lev+1:1:-1))
     77       call regr1_conserv(r_mob(j, :), press_in_edg, &
     78            p3d(1, j, nbp_lev + 1:1:-1), o3_mob_regr(1, j, nbp_lev:1:-1))
    7979       ! (invert order of indices because "p3d" is in descending order)
    8080    end do
     
    8383    do j = 2, nbp_lat-1
    8484       do i = 1, nbp_lon
    85           o3_mob_regr(i, j, nbp_lev:1:-1) &
    86                = regr1_step_av(r_mob(j, :), press_in_edg, &
    87                p3d(i, j, nbp_lev+1:1:-1))
    88              ! (invert order of indices because "p3d" is in descending order)
     85          call regr1_conserv(r_mob(j, :), press_in_edg, &
     86               p3d(i, j, nbp_lev + 1:1:-1), o3_mob_regr(i, j, nbp_lev:1:-1))
     87          ! (invert order of indices because "p3d" is in descending order)
    8988       end do
    9089    end do
Note: See TracChangeset for help on using the changeset viewer.