Ignore:
Timestamp:
Jan 8, 2016, 9:52:14 AM (9 years ago)
Author:
ymipsl
Message:
  • Switch to XIOS 2
  • Append main part of forcing configuration (LMDZ stand alone)
  • Create etat0 and limit from usual LMDZ input files, using XIOS 2 interpolation functionnalities
    • missing parametrization of gravity waves
    • missing aerosol
File:
1 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_climoz_m.F90

    r3825 r3867  
    1111contains
    1212
    13   subroutine regr_lat_time_climoz(read_climoz)
     13  subroutine regr_lat_time_climoz(read_climoz, regr_lat)
    1414
    1515    ! "regr_lat_time_climoz" stands for "regrid latitude time
     
    6565    ! periodicity for interpolation at the beginning and at the end of the
    6666    ! year.
    67     use mod_grid_phy_lmdz, ONLY : nbp_lat
     67    use mod_grid_phy_lmdz, ONLY : nbp_lat, grid_type, unstructured
    6868    use regr1_step_av_m, only: regr1_step_av
    6969    use regr3_lint_m, only: regr3_lint
     
    7575    use regular_lonlat_mod, only : boundslat_reg, south
    7676    use nrtype, only: pi
     77    use regular_lonlat_mod, only : lat_reg
     78    implicit none
    7779    integer, intent(in):: read_climoz ! read ozone climatology
    7880    ! Allowed values are 1 and 2
     
    8284
    8385    ! Variables local to the procedure:
     86    LOGICAL, intent(in), OPTIONAL :: regr_lat
    8487
    8588    integer n_plev ! number of pressure levels in the input data
    8689    integer n_lat ! number of latitudes in the input data
    8790    integer n_month ! number of months in the input data
     91    integer n_lat_out ! number of latitudes in the output data
    8892
    8993    real, pointer:: latitude(:)
     
    158162    ! (time to middle of day, in days since January 1st 0h, in a
    159163    ! 360-day calendar)
    160 
     164    logical :: regr_lat_
     165    REAL,ALLOCATABLE :: lat_out(:)
     166   
    161167    !---------------------------------
     168    IF (PRESENT(regr_lat)) THEN
     169      regr_lat_=regr_lat
     170    ELSE
     171      regr_lat_=.TRUE.
     172    ENDIF
    162173
    163174    print *, "Call sequence information: regr_lat_time_climoz"
     
    183194    forall (j = 2:n_lat) lat_in_edg(j) = (latitude(j - 1) + latitude(j)) / 2
    184195    lat_in_edg(n_lat + 1) = pi / 2
    185     deallocate(latitude) ! pointer
    186196
    187197    call nf95_inq_varid(ncid_in, "plev", varid)
     
    204214    end if
    205215
     216    IF (regr_lat_) THEN
     217      n_lat_out=nbp_lat
     218      ALLOCATE(lat_out(n_lat_out))
     219      lat_out=lat_reg
     220    ELSE
     221      n_lat_out=n_lat
     222      ALLOCATE(lat_out(n_lat_out))
     223      lat_out=latitude
     224    ENDIF
     225
    206226    ! Create the output file and get the variable IDs:
    207     call prepare_out(ncid_in, n_plev, ncid_out, varid_out, varid_plev, &
     227    call prepare_out(ncid_in, n_lat_out, lat_out, n_plev, ncid_out, varid_out, varid_plev, &
    208228         varid_time)
     229
     230    deallocate(latitude) ! pointer
    209231
    210232    ! Write remaining coordinate variables:
     
    281303    call nf95_close(ncid_in)
    282304
    283     allocate(o3_regr_lat(nbp_lat, n_plev, 0:13, read_climoz))
    284     allocate(o3_out(nbp_lat, n_plev, 360, read_climoz))
    285 
    286     ! Regrid in latitude:
    287     ! We average with respect to sine of latitude, which is
    288     ! equivalent to weighting by cosine of latitude:
    289     if (n_month == 12) then
    290        print *, &
    291             "Found 12 months in ozone climatologies, assuming periodicity..."
    292        o3_regr_lat(nbp_lat:1:-1, :, 1:12, :) = regr1_step_av(o3_in, &
    293             xs=sin(lat_in_edg), xt=sin((/- pi / 2, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
    294        ! (invert order of indices in "o3_regr_lat" because "rlatu" is
    295        ! in descending order)
    296 
    297        ! Duplicate January and December values, in preparation of time
    298        ! interpolation:
    299        o3_regr_lat(:, :, 0, :) = o3_regr_lat(:, :, 12, :)
    300        o3_regr_lat(:, :, 13, :) = o3_regr_lat(:, :, 1, :)
    301     else
    302        print *, "Using 14 months in ozone climatologies..."
    303        o3_regr_lat(nbp_lat:1:-1, :, :, :) = regr1_step_av(o3_in, &
    304             xs=sin(lat_in_edg), xt=sin((/- pi / 2, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
    305        ! (invert order of indices in "o3_regr_lat" because "rlatu" is
    306        ! in descending order)
    307     end if
    308 
    309     ! Regrid in time by linear interpolation:
    310     o3_out = regr3_lint(o3_regr_lat, tmidmonth, tmidday)
     305    allocate(o3_out(n_lat_out, n_plev, 360, read_climoz))
     306    IF (regr_lat) THEN
     307      allocate(o3_regr_lat(nbp_lat, n_plev, 0:13, read_climoz))
     308
     309      ! Regrid in latitude:
     310      ! We average with respect to sine of latitude, which is
     311      ! equivalent to weighting by cosine of latitude:
     312      if (n_month == 12) then
     313         print *, &
     314              "Found 12 months in ozone climatologies, assuming periodicity..."
     315         o3_regr_lat(nbp_lat:1:-1, :, 1:12, :) = regr1_step_av(o3_in, &
     316              xs=sin(lat_in_edg), xt=sin((/- pi / 2, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
     317         ! (invert order of indices in "o3_regr_lat" because "rlatu" is
     318         ! in descending order)
     319
     320         ! Duplicate January and December values, in preparation of time
     321         ! interpolation:
     322         o3_regr_lat(:, :, 0, :) = o3_regr_lat(:, :, 12, :)
     323         o3_regr_lat(:, :, 13, :) = o3_regr_lat(:, :, 1, :)
     324      else
     325         print *, "Using 14 months in ozone climatologies..."
     326         o3_regr_lat(nbp_lat:1:-1, :, :, :) = regr1_step_av(o3_in, &
     327              xs=sin(lat_in_edg), xt=sin((/- pi / 2, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
     328         ! (invert order of indices in "o3_regr_lat" because "rlatu" is
     329         ! in descending order)
     330      end if
     331      ! Regrid in time by linear interpolation:
     332      o3_out = regr3_lint(o3_in, tmidmonth, tmidday)
     333    ELSE
     334      ! Regrid in time by linear interpolation:
     335      o3_out = regr3_lint(o3_in, tmidmonth, tmidday)
     336    ENDIF
    311337
    312338    ! Write to file:
     339
    313340    do m = 1, read_climoz
    314        call nf95_put_var(ncid_out, varid_out(m), o3_out(nbp_lat:1:-1, :, :, m))
     341       IF (grid_type==unstructured) THEN
     342         ! Doing spatial interpolation from XIOS need to have some point in longitude
     343         ! waiting zonal mean operation from XIOS
     344         call nf95_put_var(ncid_out, varid_out(m), SPREAD(o3_out(n_lat_out:1:-1, :, :, m),1,4))
     345       ELSE
     346         call nf95_put_var(ncid_out, varid_out(m), o3_out(n_lat_out:1:-1, :, :, m))
     347       ENDIF
     348       
    315349       ! (The order of "rlatu" is inverted in the output file)
    316350    end do
     
    322356  !********************************************
    323357
    324   subroutine prepare_out(ncid_in, n_plev, ncid_out, varid_out, varid_plev, &
     358  subroutine prepare_out(ncid_in, n_lat, lat, n_plev, ncid_out, varid_out, varid_plev, &
    325359       varid_time)
    326360
     
    328362    ! dimensions and variables, and writes one of the coordinate variables.
    329363
    330     use mod_grid_phy_lmdz, ONLY : nbp_lat
    331364    use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, &
    332365         nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
    333     use netcdf, only: nf90_clobber, nf90_float, nf90_global
     366    use netcdf, only: nf90_clobber,nf90_netcdf4, nf90_float, nf90_global, nf90_unlimited
    334367    use nrtype, only: pi
    335     use regular_lonlat_mod, only : lat_reg
    336     integer, intent(in):: ncid_in, n_plev
     368    use mod_grid_phy_lmdz, ONLY :  grid_type, unstructured
     369
     370    integer, intent(in):: ncid_in, n_lat, n_plev
     371    real, intent(in):: lat(:)
    337372    integer, intent(out):: ncid_out, varid_plev, varid_time
    338373
     
    344379
    345380    integer ncerr
    346     integer dimid_rlatu, dimid_plev, dimid_time
    347     integer varid_rlatu
     381    integer dimid_rlatu, dimid_rlonv, dimid_plev, dimid_time
     382    integer varid_rlonv, varid_rlatu
    348383
    349384    !---------------------------
     
    351386    print *, "Call sequence information: prepare_out"
    352387
    353     call nf95_create("climoz_LMDZ.nc", nf90_clobber, ncid_out)
     388    call nf95_create("climoz_LMDZ.nc", NF90_CLOBBER + NF90_NETCDF4, ncid_out)
    354389
    355390    ! Dimensions:
    356     call nf95_def_dim(ncid_out, "time", 360, dimid_time)
     391    call nf95_def_dim(ncid_out, "time",  nf90_unlimited, dimid_time)
    357392    call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
    358     call nf95_def_dim(ncid_out, "rlatu", nbp_lat, dimid_rlatu)
     393    call nf95_def_dim(ncid_out, "rlatu", n_lat, dimid_rlatu)
     394    if (grid_type==unstructured) call nf95_def_dim(ncid_out, "rlonv", 4, dimid_rlonv)
    359395
    360396    ! Define coordinate variables:
     
    374410    call nf95_put_att(ncid_out, varid_rlatu, "standard_name", "latitude")
    375411
     412    if (grid_type==unstructured) then
     413      call nf95_def_var(ncid_out, "rlonv", nf90_float, dimid_rlonv, varid_rlonv)
     414      call nf95_put_att(ncid_out, varid_rlonv, "units", "degrees_east")
     415      call nf95_put_att(ncid_out, varid_rlonv, "standard_name", "longitude")
     416    endif
     417   
    376418    ! Define the primary variables:
    377419
    378     call nf95_def_var(ncid_out, "tro3", nf90_float, &
     420    if (grid_type==unstructured) then
     421        call nf95_def_var(ncid_out, "tro3", nf90_float, &
     422         (/dimid_rlonv, dimid_rlatu, dimid_plev, dimid_time/), varid_out(1))
     423    else
     424        call nf95_def_var(ncid_out, "tro3", nf90_float, &
    379425         (/dimid_rlatu, dimid_plev, dimid_time/), varid_out(1))
     426    endif 
     427   
    380428    call nf95_put_att(ncid_out, varid_out(1), "long_name", &
    381429         "ozone mole fraction")
     
    384432
    385433    if (size(varid_out) == 2) then
    386        call nf95_def_var(ncid_out, "tro3_daylight", nf90_float, &
    387             (/dimid_rlatu, dimid_plev, dimid_time/), varid_out(2))
     434      if (grid_type==unstructured) then
     435         call nf95_def_var(ncid_out, "tro3_daylight", nf90_float, &
     436             (/dimid_rlonv, dimid_rlatu, dimid_plev, dimid_time/), varid_out(2))
     437      else
     438         call nf95_def_var(ncid_out, "tro3_daylight", nf90_float, &
     439             (/ dimid_rlatu, dimid_plev, dimid_time/), varid_out(2))
     440      endif
     441       
    388442       call nf95_put_att(ncid_out, varid_out(2), "long_name", &
    389443            "ozone mole fraction in daylight")
     
    417471
    418472    ! Write one of the coordinate variables:
    419     call nf95_put_var(ncid_out, varid_rlatu, lat_reg(nbp_lat:1:-1) / pi * 180.)
     473    call nf95_put_var(ncid_out, varid_rlatu, lat(n_lat:1:-1) / pi * 180.)
    420474    ! (convert from rad to degrees and sort in ascending order)
     475    if (grid_type==unstructured)  call nf95_put_var(ncid_out, varid_rlonv, (/ 0., 90., 180.,270. /))
    421476
    422477  contains
Note: See TracChangeset for help on using the changeset viewer.