Changeset 3629 for LMDZ5


Ignore:
Timestamp:
Feb 10, 2020, 9:54:26 AM (4 years ago)
Author:
acozic
Message:

Add new grid, new axis and new variables for cmip protocole and dr2xml

  • field_group id="coord_hyb"
  • grid_ref="klevp1_bnds"
  • grid_ref="klev_bnds"
  • domain id="greordered"
  • axis id="axis_lat"
  • axis id="bnds"
  • axis id="klevp1"
  • axis id="klev"
Location:
LMDZ5/branches/IPSLCM5A2.1
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/IPSLCM5A2.1/DefLists/context_lmdz.xml

    r3618 r3629  
    2525  <domain_definition>
    2626    <domain id="dom_glo" data_dim="2" />
     27    <domain id="greordered"  domain_ref="dom_glo">
     28      <reorder_domain invert_lat="true" shift_lon_fraction="0.5" min_lon="0" max_lon="360" />
     29    </domain>
    2730  </domain_definition>
    2831 
     
    3336
    3437  <grid_definition>
     38
     39    <grid id="klev_bnds"> <axis axis_ref="klev" /> <axis axis_ref="bnds" /> </grid>
     40    <grid id="klevp1_bnds"> <axis axis_ref="klevp1" /> <axis axis_ref="bnds" /> </grid>
     41
    3542     <grid id="grid_glo">
    3643        <domain domain_ref="dom_glo" />
     
    9299    <axis id="Bhyb" standard_name="Bhyb comp of Hyb Cord" unit="">
    93100    </axis>
     101    <axis id="Ahyb_inter" standard_name="A comp of Hyb Cord at interface" unit="Pa">
     102    </axis>
     103    <axis id="Bhyb_inter" standard_name="B comp of Hyb Cord at interface" unit="">
     104    </axis>
    94105    <axis id="Alt" standard_name="Height approx for scale heigh of 8km at levels" unit="km">
    95106    </axis>
    96107    <axis id="plev" standard_name="model_level_number" unit="Pa">
     108    </axis>
     109    <axis id="klev"  prec="8" long_name = "number of layers"
     110          standard_name ="number of layers" unit="1">
     111    </axis>
     112    <axis id="klevp1"  prec="8" long_name = "number of layer interfaces"
     113          standard_name ="number of layer interfaces" unit="1">
     114    </axis>
     115    <axis id="bnds" standard_name="bounds" unit="1" >
     116    </axis>
     117    <axis id="axis_lat" standard_name="Latitude axis">
     118        <reduce_domain operation="average" direction="iDir" />
    97119    </axis>
    98120
     
    113135    </axis>
    114136
     137
    115138  </axis_definition>
    116139</context>
  • LMDZ5/branches/IPSLCM5A2.1/DefLists/field_def_lmdz.xml

    r3618 r3629  
    77<!--    </field_group>  -->
    88   
     9    <field_group id="coordinates" grid_ref="grid_glo">
     10        <field id="io_lon"  />
     11        <field id="io_lat"  />
     12    </field_group>
     13
     14    <field_group id="coord_hyb">
     15      <field id="Ahyb" long_name="Ahyb at level interface"     axis_ref="klevp1" />
     16      <field id="Ahyb_bounds" long_name="" grid_ref="klevp1_bnds" />
     17      <field id="Bhyb" long_name="Bhyb at level interface"       axis_ref="klevp1"  />
     18      <field id="Bhyb_bounds" long_name=""  grid_ref="klevp1_bnds" />
     19      <field id="Ahyb_mid" long_name="Ahyb at the middle of the level"      axis_ref="klev" />
     20      <field id="Ahyb_mid_bounds" long_name="" grid_ref="klev_bnds" />
     21      <field id="Bhyb_mid" long_name="Bhyb at the middle of the level"       axis_ref="klev"  />
     22      <field id="Bhyb_mid_bounds" long_name=""  grid_ref="klev_bnds" />
     23    </field_group>
     24
    925    <field_group id="fields_2D" grid_ref="grid_glo">
    1026        <field id="phis"    long_name="Surface geop.height"     unit="m2/s2" />
  • LMDZ5/branches/IPSLCM5A2.1/libf/dyn3d_common/disvert.F90

    r2603 r3629  
    1010  use new_unit_m, only: new_unit
    1111  use assert_m, only: assert
    12   USE comvert_mod, ONLY: ap, bp, nivsigs, nivsig, dpres, presnivs, &
    13                          pa, preff, scaleheight
     12  USE comvert_mod, ONLY: ap, bp, aps, bps, nivsigs, nivsig, dpres, presnivs, &
     13                         pseudoalt, pa, preff, scaleheight
    1414  USE logic_mod, ONLY: ok_strato
    1515
     
    346346  DO l = 1, llm
    347347     dpres(l) = bp(l) - bp(l+1)
     348     aps(l) =  0.5 *( ap(l) +ap(l+1))
     349     bps(l) =  0.5 *( bp(l) +bp(l+1))
    348350     presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
     351     pseudoalt(l) = log(preff/presnivs(l))*scaleheight
    349352     write(lunout, *)'PRESNIVS(', l, ')=', presnivs(l), ' Z ~ ', &
    350           log(preff/presnivs(l))*scaleheight &
     353          pseudoalt(l) &
    351354          , ' DZ ~ ', scaleheight*log((ap(l)+bp(l)*preff)/ &
    352355          max(ap(l+1)+bp(l+1)*preff, 1.e-10))
  • LMDZ5/branches/IPSLCM5A2.1/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r2610 r3629  
    1212                     prad,pg,pr,pcpp,iflag_phys)
    1313  USE dimphy, ONLY: init_dimphy
    14   USE comvert_mod, ONLY: preff, ap, bp, presnivs, scaleheight, pseudoalt
     14  USE comvert_mod, ONLY: preff, ap, bp, aps, bps, presnivs, &
     15                         scaleheight, pseudoalt
    1516  USE inigeomphy_mod, ONLY: inigeomphy
    1617  USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat,nbp_lev,klon_glo ! number of atmospheric columns (on full grid)
     
    103104!$OMP COPYIN(annee_ref, day_ini, day_ref, start_time)
    104105
    105   ! copy over preff , ap(), bp(), etc 
     106  ! copy over preff , ap(), bp(), etc
    106107  CALL init_vertical_layers(nlayer,preff,scaleheight, &
    107                             ap,bp,presnivs,pseudoalt)
     108                            ap,bp,aps,bps,presnivs,pseudoalt)
    108109
    109110  ! Initialize physical constants in physics:
  • LMDZ5/branches/IPSLCM5A2.1/libf/misc/wxios.F90

    r2509 r3629  
    342342        CALL xios_set_domain_attr_hdl(dom, nj_glo=nj_glo, jbegin=jbegin-1, nj=nj, data_dim=2)
    343343        CALL xios_set_domain_attr_hdl(dom, lonvalue_1d=io_lon(ibegin:iend), latvalue_1d=io_lat(jbegin:jend))
     344        IF (xios_is_valid_axis("axis_lat")) THEN
     345           CALL xios_set_axis_attr( "axis_lat", n_glo=nj_glo, n=nj, begin=jbegin-1, value=io_lat(jbegin:jend))
     346        ENDIF
    344347#endif
    345348        IF (.NOT.is_sequential) THEN
     
    372375    ! Pour déclarer un axe vertical !!!!!!!!!!!!!!!
    373376    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    374     SUBROUTINE wxios_add_vaxis(axis_id, axis_size, axis_value)
     377    SUBROUTINE wxios_add_vaxis(axis_id, axis_size, axis_value,     &
     378                               positif, bnds)
    375379        USE print_control_mod, ONLY : prt_level, lunout
    376380        IMPLICIT NONE
     
    379383        INTEGER, INTENT(IN) :: axis_size
    380384        REAL, DIMENSION(axis_size), INTENT(IN) :: axis_value
     385        CHARACTER (len=*), INTENT(IN), OPTIONAL :: positif
     386        REAL, DIMENSION(axis_size, 2), INTENT(IN), OPTIONAL :: bnds
    381387       
    382388!        TYPE(xios_axisgroup) :: axgroup
     
    404410        CALL xios_set_axis_attr(trim(axis_id),size=axis_size,value=axis_value)
    405411#else
    406         CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value)
     412        if (PRESENT(positif) .AND. PRESENT(bnds)) then
     413          CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value, &
     414                                  positive=positif, bounds=bnds)
     415        else if (PRESENT(positif)) then
     416          CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value, &
     417                                  positive=positif)
     418        else if (PRESENT(bnds)) then
     419          CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value, &
     420                                  bounds=bnds)
     421        else
     422          CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value)
     423        endif
    407424#endif       
    408425        !Vérification:
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/iophy.F90

    r2529 r3629  
    884884! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
    885885  SUBROUTINE histwrite2d_phy(var,field, STD_iff)
    886   USE dimphy, only: klon
    887   USE mod_phys_lmdz_para, only: gather_omp, grid1dto2d_mpi, &
     886  USE dimphy, ONLY: klon, klev
     887  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1dto2d_mpi, &
    888888                                jj_nb, klon_mpi, klon_mpi_begin, &
    889889                                klon_mpi_end, is_sequential
     
    917917    REAL, ALLOCATABLE, DIMENSION(:) :: fieldok
    918918
    919     IF (prt_level >= 10) THEN
     919!    IF (prt_level >= 10) THEN
    920920      WRITE(lunout,*)'Begin histwrite2d_phy for ',trim(var%name)
    921     ENDIF
     921!    ENDIF
    922922! ug RUSTINE POUR LES STD LEVS.....
    923923      IF (PRESENT(STD_iff)) THEN
     
    948948
    949949    !Et sinon on.... écrit
    950     IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_phy','Field first DIMENSION not equal to klon',1)
     950    IF (SIZE(field)/=klon .AND. SIZE(field)/=klev .AND. SIZE(field)/=klev+1) CALL abort_physic('iophy::histwrite2d_phy','Field first DIMENSION not equal to klon/klev',1)   
     951    IF (prt_level >= 10) THEn
     952      WRITE (lunout,*)"histwrite2d_phy: .not.vars_defined ; time to gather and write ", trim(var%name)
     953    ENDIF
    951954   
    952     if (prt_level >= 10) then
    953       write(lunout,*)"histwrite2d_phy: .not.vars_defined ; time to gather and write ", &
    954                      trim(var%name)
    955     endif
    956955   
    957     CALL Gather_omp(field,buffer_omp)
     956    IF (SIZE(field) == klon) then
     957        CALL Gather_omp(field,buffer_omp)
     958    ELSE
     959        buffer_omp(:)=0.
     960    ENDIF
    958961!$OMP MASTER
    959962    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
     
    964967      IF (ok_all_xml) THEN
    965968#ifdef CPP_XIOS
    966           if (prt_level >= 10) then
    967              write(lunout,*)'Dans iophy histwrite2D,var%name ',&
    968                              trim(var%name)                       
    969           endif
    970           CALL xios_send_field(var%name, Field2d)
    971           if (prt_level >= 10) then
    972              write(lunout,*)'Dans iophy histwrite2D,var%name apres xios_send ',&
    973                              trim(var%name)                       
    974           endif
     969          IF (prt_level >= 10) THEN
     970             write(lunout,*)'Dans iophy histwrite2D,var%name ', trim(var%name)                       
     971          ENDIF
     972          IF (SIZE(field) == klon) then
     973              CALL xios_send_field(var%name, Field2d)
     974          ELSE
     975             CALL xios_send_field(var%name, field)
     976          ENDIF
     977          IF (prt_level >= 10) THEN
     978             WRITE (lunout,*)'Dans iophy histwrite2D,var%name apres xios_send ', trim(var%name)                       
     979          ENDIF
    975980#else
    976981        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     
    982987#ifdef CPP_XIOS
    983988               IF (firstx) THEN
    984                   if (prt_level >= 10) then
    985                      write(lunout,*)'Dans iophy histwrite2D,iff,var%name ',&
    986                                     iff,trim(var%name)                       
    987                      write(lunout,*)"histwrite2d_phy:.NOT.clef_stations(iff)and iff==iff_beg, call xios_send_field"
    988                   endif
    989                   CALL xios_send_field(var%name, Field2d)
     989                  IF (prt_level >= 10) THEN
     990                     WRITE (lunout,*)'Dans iophy histwrite2D,iff,var%name ', iff,trim(var%name)                       
     991                     WRITE (lunout,*)"histwrite2d_phy:.NOT.clef_stations(iff)and iff==iff_beg, call xios_send_field"
     992                  ENDIF
     993                  IF (SIZE(field) == klon) then
     994                     CALL xios_send_field(var%name, Field2d)
     995                  ELSE
     996                     CALL xios_send_field(var%name, field)
     997                  ENDIF
    990998                  firstx=.false.
    991999               ENDIF
     
    10831091            iff_beg = 1
    10841092            iff_end = nfiles
    1085       END IF
     1093      ENDIF
    10861094
    10871095  ! On regarde si on est dans la phase de définition ou d'écriture:
     
    10971105  ELSE
    10981106    !Et sinon on.... écrit
    1099     IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     1107
     1108    IF (SIZE(field,1)/=klon .AND. SIZE(field,1)/=klev .AND. SIZE(field,1)/=klev+1) CALL abort_physic('iophy::histwrite3d_phy','Field first DIMENSION not equal to klon/klev',1)
     1109
    11001110    nlev=SIZE(field,2)
    11011111    if (nlev.eq.klev+1) then
     
    11051115    endif
    11061116
    1107     CALL Gather_omp(field,buffer_omp)
     1117    IF (SIZE(field,1) == klon) then
     1118        CALL Gather_omp(field,buffer_omp)
     1119    ELSE
     1120        buffer_omp(:,:)=0.
     1121    ENDIF
    11081122!$OMP MASTER
    11091123    CALL grid1Dto2D_mpi(buffer_omp,field3d)
     
    11181132             write(lunout,*)'Dans iophy histwrite3D,var%name ',&
    11191133                             trim(var%name)                       
    1120           endif
    1121           CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     1134          ENDIF
     1135          IF (SIZE(field,1) == klon) then
     1136             CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     1137          ELSE
     1138             CALL xios_send_field(var%name, field)
     1139          ENDIF
    11221140#else
    11231141        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     
    11361154                                  trim(var%name), ' with iim jjm nlevx = ', &
    11371155                                  nbp_lon,jj_nb,nlevx
    1138                 endif
    1139                 CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
    1140                             firstx=.false.
     1156                ENDIF
     1157                IF (SIZE(field,1) == klon) then
     1158                    CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     1159                ELSE
     1160                     CALL xios_send_field(var%name, field)
     1161                ENDIF
     1162                firstx=.false.
    11411163              ENDIF
    11421164#endif
     
    11941216#ifdef CPP_XIOS
    11951217  SUBROUTINE histwrite2d_xios(field_name,field)
    1196   USE dimphy, only: klon
    1197   USE mod_phys_lmdz_para, only: gather_omp, grid1Dto2D_mpi, &
     1218  USE dimphy, ONLY: klon, klev
     1219  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1Dto2D_mpi, &
    11981220                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    11991221                                jj_nb, klon_mpi
     
    12171239
    12181240    !Et sinon on.... écrit
    1219     IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
     1241    IF (SIZE(field)/=klon .AND. SIZE(field)/=klev .AND. SIZE(field)/=klev+1) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon/klev',1)
    12201242   
    1221     CALL Gather_omp(field,buffer_omp)   
     1243    IF (SIZE(field) == klev .OR. SIZE(field) == klev+1) then
     1244!$OMP MASTER
     1245        CALL xios_send_field(field_name,field)
     1246!$OMP END MASTER   
     1247    ELSE
     1248        CALL Gather_omp(field,buffer_omp)   
    12221249!$OMP MASTER
    12231250    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
     
    12571284    deallocate(fieldok)
    12581285!$OMP END MASTER   
     1286    ENDIF
    12591287
    12601288  IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite2d_xios ',field_name
     
    12861314
    12871315    !Et on.... écrit
    1288     IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
    1289     nlev=SIZE(field,2)
     1316    IF (SIZE(field,1)/=klon .AND. SIZE(field,1)/=klev .AND. SIZE(field,1)/=klev+1) then
     1317      write(lunout,*)' histrwrite3d_xios ', field_name, SIZE(field)
     1318      CALL abort_physic('iophy::histwrite3d_xios','Field first DIMENSION not equal to klon/klev',1)
     1319    ENDIF
     1320   
     1321    IF (SIZE(field,1) == klev .OR. SIZE(field,1) == klev+1) then
     1322!$OMP MASTER
     1323        CALL xios_send_field(field_name,field)
     1324!$OMP END MASTER   
     1325    ELSE
     1326        nlev=SIZE(field,2)
    12901327
    12911328
     
    13281365    deallocate(fieldok)
    13291366!$OMP END MASTER   
     1367    ENDIF
    13301368
    13311369  IF (prt_level >= 10) write(lunout,*)'End histrwrite3d_xios ',field_name
    13321370  END SUBROUTINE histwrite3d_xios
     1371
     1372#ifdef CPP_XIOS
     1373  SUBROUTINE histwrite0d_xios(field_name, field)
     1374  USE xios, ONLY: xios_send_field
     1375  IMPLICIT NONE
     1376
     1377    CHARACTER(LEN=*), INTENT(IN) :: field_name
     1378    REAL, INTENT(IN) :: field ! --> scalar
     1379
     1380!$OMP MASTER
     1381   CALL xios_send_field(field_name, field)
     1382!$OMP END MASTER
     1383
     1384  END SUBROUTINE histwrite0d_xios
     1385#endif
     1386
    13331387#endif
    13341388end module iophy
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/phys_output_ctrlout_mod.F90

    r2580 r3629  
    1717!  CHARACTER(len=20), dimension(nfiles) :: TEF = type_ecri_files
    1818
    19 !!! Comosantes de la coordonnee sigma-hybride
    20 !!! Ap et Bp
    21   TYPE(ctrl_out), SAVE :: o_Ahyb = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11 /), &
    22     'Ap', '', '', (/ ('', i=1, 9) /))
    23   TYPE(ctrl_out), SAVE :: o_Bhyb = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11 /), &
    24     'Bp', '', '', (/ ('', i=1, 9) /))
    25   TYPE(ctrl_out), SAVE :: o_Alt = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11 /), &
     19!!! saving lon and lat as variables for CMIP6 DataRequest
     20  TYPE(ctrl_out), SAVE :: o_longitude = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     21    'io_lon', '', '', (/ ('once', i=1, 9) /))
     22  TYPE(ctrl_out), SAVE :: o_latitude = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     23    'io_lat', '', '', (/ ('once', i=1, 9) /))
     24
     25!!! Composantes de la coordonnee sigma-hybride
     26!!! Ap et Bp et interfaces
     27  TYPE(ctrl_out), SAVE :: o_Ahyb = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     28    'Ahyb', 'Ahyb at level interface', '', (/ ('once', i=1, 9) /))
     29  TYPE(ctrl_out), SAVE :: o_Bhyb = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     30    'Bhyb', 'Bhyb at level interface', '', (/ ('once', i=1, 9) /))
     31  TYPE(ctrl_out), SAVE :: o_Ahyb_bounds = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     32    'Ahyb_bounds', '', '', (/ ('once', i=1, 9) /))
     33  TYPE(ctrl_out), SAVE :: o_Bhyb_bounds = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     34    'Bhyb_bounds', '', '', (/ ('once', i=1, 9) /))
     35!!! Composantes de la coordonnee sigma-hybride  au milieu des couches
     36!!! Aps et Bps et interfaces
     37  TYPE(ctrl_out), SAVE :: o_Ahyb_mid = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     38    'Ahyb_mid', 'Ahyb at the middle of the level', '', (/ ('once', i=1, 9) /))
     39  TYPE(ctrl_out), SAVE :: o_Bhyb_mid = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     40    'Bhyb_mid', 'Bhyb at the middle of the level', '', (/ ('once', i=1, 9) /))
     41  TYPE(ctrl_out), SAVE :: o_Ahyb_mid_bounds = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     42    'Ahyb_mid_bounds', '', '', (/ ('once', i=1, 9) /))
     43  TYPE(ctrl_out), SAVE :: o_Bhyb_mid_bounds = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
     44    'Bhyb_mid_bounds', '', '', (/ ('once', i=1, 9) /))
     45
     46  TYPE(ctrl_out), SAVE :: o_Alt = ctrl_out((/ 1, 1, 1, 1, 1, 1, 11, 11, 11/), &
    2647    'Alt', '', '', (/ ('', i=1, 9) /))
    2748
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/phys_output_mod.F90

    r2907 r3629  
    4646    USE mod_grid_phy_lmdz, only: klon_glo,nbp_lon,nbp_lat
    4747    USE print_control_mod, ONLY: prt_level,lunout
    48     USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, Ahyb, Bhyb
     48    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, aps, bps, pseudoalt
    4949    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
    5050#ifdef CPP_XIOS
     
    130130    REAL, DIMENSION(nfiles), SAVE     :: phys_out_latmax        = (/  90.,     90.,     90.,     90., &
    131131                                                                    90., 90., 90., 90., 90. /)                       
     132    REAL, DIMENSION(klev,2) :: Ahyb_bounds, Bhyb_bounds
     133    REAL, DIMENSION(klev+1)   :: lev_index
    132134#ifdef CPP_XIOS
    133135    ! ug Variables utilis\'ees pour r\'ecup\'erer le calendrier pour xios
     
    140142    WRITE(lunout,*) 'Debut phys_output_mod.F90'
    141143    ! Initialisations (Valeurs par defaut
     144
     145    DO ilev=1,klev
     146      Ahyb_bounds(ilev,1) = ap(ilev)
     147      Ahyb_bounds(ilev,2) = ap(ilev+1)
     148      Bhyb_bounds(ilev,1) = bp(ilev)
     149      Bhyb_bounds(ilev,2) = bp(ilev+1)
     150      lev_index(ilev) = REAL(ilev)
     151    END DO
     152      lev_index(klev+1) = REAL(klev+1)
    142153
    143154    IF (.NOT. ALLOCATED(o_trac)) ALLOCATE(o_trac(nqtot))
     
    283294    zdtime_moy = dtime         ! Frequence ou l on moyenne
    284295
    285     ! Calcul des Ahyb, Bhyb et Alt
    286     DO k=1,klev
    287        Ahyb(k)=(ap(k)+ap(k+1))/2.
    288        Bhyb(k)=(bp(k)+bp(k+1))/2.
    289        Alt(k)=log(preff/presnivs(k))*8.
    290     ENDDO
    291     !          if(prt_level.ge.1) then
    292     WRITE(lunout,*)'Ap Hybrid = ',Ahyb(1:klev)
    293     WRITE(lunout,*)'Bp Hybrid = ',Bhyb(1:klev)
    294     WRITE(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)
    295     !          endif
    296296
    297297  ecrit_files(7) = ecrit_files(1)
     
    335335            levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
    336336    CALL wxios_add_vaxis("Ahyb", &
    337             levmax(iff) - levmin(iff) + 1, Ahyb)
     337            levmax(iff) - levmin(iff) + 1, aps(levmin(iff):levmax(iff)), positif='down', &
     338            bnds=Ahyb_bounds(levmin(iff):levmax(iff),:))
    338339    CALL wxios_add_vaxis("Bhyb", &
    339             levmax(iff) - levmin(iff) + 1, Bhyb)
    340     CALL wxios_add_vaxis("Alt", &
    341             levmax(iff) - levmin(iff) + 1, Alt)
    342    else
     340            levmax(iff) - levmin(iff) + 1, bps(levmin(iff):levmax(iff)), positif='down', &
     341            bnds=Bhyb_bounds(levmin(iff):levmax(iff),:))
     342    CALL wxios_add_vaxis("klev", levmax(iff) - levmin(iff) + 1, &
     343                          lev_index(levmin(iff):levmax(iff)))
     344    CALL wxios_add_vaxis("klevp1", klev+1, &
     345                          lev_index(1:klev+1))
     346    CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
     347
     348     CALL wxios_add_vaxis("Alt", &
     349            levmax(iff) - levmin(iff) + 1, pseudoalt)
     350
     351   ELSE
    343352    ! NMC files
    344353    CALL wxios_add_vaxis("plev", &
     
    403412!!!! Composantes de la coordonnee sigma-hybride
    404413          CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
    405                levmax(iff) - levmin(iff) + 1,Ahyb,nvertap(iff))
     414               levmax(iff) - levmin(iff) + 1,aps,nvertap(iff))
    406415
    407416          CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
    408                levmax(iff) - levmin(iff) + 1,Bhyb,nvertbp(iff))
     417               levmax(iff) - levmin(iff) + 1,bps,nvertbp(iff))
    409418
    410419          CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &                       
    411                levmax(iff) - levmin(iff) + 1,Alt,nvertAlt(iff))
     420               levmax(iff) - levmin(iff) + 1,pseudoalt,nvertAlt(iff))
    412421
    413422          else
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/phys_output_write_mod.F90

    r3606 r3629  
    2727    USE mod_phys_lmdz_para, ONLY: is_north_pole_phy,is_south_pole_phy
    2828    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    29     USE time_phylmdz_mod, only: day_step_phy, start_time, itau_phy
    30     USE phys_output_ctrlout_mod, only: o_phis, o_aire, is_ter, is_lic, is_oce, &
     29    USE time_phylmdz_mod, ONLY: day_step_phy, start_time, itau_phy
     30    USE vertical_layers_mod, ONLY : ap, bp, aps, bps
     31    USE phys_output_ctrlout_mod, ONLY: o_phis, o_aire, is_ter, is_lic, is_oce, &
     32         o_longitude, o_latitude, &
     33         o_Ahyb, o_Bhyb,o_Ahyb_bounds, o_Bhyb_bounds, &
     34         o_Ahyb_mid, o_Bhyb_mid,o_Ahyb_mid_bounds, o_Bhyb_mid_bounds, &
    3135         is_ave, is_sic, o_contfracATM, o_contfracOR, &
    3236         o_aireTER, o_flat, o_slp, o_ptstar, o_pt0, o_tsol, &
     
    295299    USE indice_sol_mod, only: nbsrf
    296300    USE infotrac_phy, only: nqtot, nqo, type_trac
    297     USE geometry_mod, only: cell_area
     301    USE geometry_mod, only: cell_area, latitude_deg, longitude_deg
    298302    USE surface_data, only: type_ocean, version_ocean, ok_veget, ok_snow
    299303!    USE aero_mod, only: naero_spc
     
    351355    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
    352356!   REAL, PARAMETER :: missing_val=nf90_fill_real
     357    REAL, DIMENSION(klev+1,2) :: Ahyb_bounds, Bhyb_bounds
     358    REAL, DIMENSION(klev,2) :: Ahyb_mid_bounds, Bhyb_mid_bounds
     359    INTEGER :: ilev
    353360#ifndef CPP_XIOS
    354361    REAL :: missing_val
     
    367374    ENDIF
    368375
    369     ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
     376    Ahyb_bounds(1,1) = 0.
     377    Ahyb_bounds(1,2) = aps(1)
     378    Bhyb_bounds(1,1) = 1.
     379    Bhyb_bounds(1,2) = bps(1)   
     380    DO ilev=2,klev
     381      Ahyb_bounds(ilev,1) = aps(ilev-1)
     382      Ahyb_bounds(ilev,2) = aps(ilev)
     383      Bhyb_bounds(ilev,1) = bps(ilev-1)
     384      Bhyb_bounds(ilev,2) = bps(ilev)
     385    ENDDO
     386     Ahyb_bounds(klev+1,1) = aps(klev)
     387     Ahyb_bounds(klev+1,2) = 0.
     388     Bhyb_bounds(klev+1,1) = bps(klev)
     389     Bhyb_bounds(klev+1,2) = 0.
     390
     391    DO ilev=1, klev
     392      Ahyb_mid_bounds(ilev,1) = ap(ilev)
     393      Ahyb_mid_bounds(ilev,2) = ap(ilev+1)
     394      Bhyb_mid_bounds(ilev,1) = bp(ilev)
     395      Bhyb_mid_bounds(ilev,2) = bp(ilev+1)
     396    END DO   
     397
     398! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
    370399    DO iinit=1, iinitend
    371400#ifdef CPP_XIOS
     
    403432       CALL histwrite_phy(o_contfracOR, pctsrf(:,is_ter))
    404433       CALL histwrite_phy(o_aireTER, paire_ter)
     434#ifdef CPP_XIOS
     435       CALL histwrite_phy(o_Ahyb, ap)
     436       CALL histwrite_phy(o_Bhyb, bp)
     437       CALL histwrite_phy(o_Ahyb_bounds, Ahyb_bounds)
     438       CALL histwrite_phy(o_Bhyb_bounds, Bhyb_bounds)
     439       CALL histwrite_phy(o_Ahyb_mid, aps)
     440       CALL histwrite_phy(o_Bhyb_mid, bps)
     441       CALL histwrite_phy(o_Ahyb_mid_bounds, Ahyb_mid_bounds)
     442       CALL histwrite_phy(o_Bhyb_mid_bounds, Bhyb_mid_bounds)
     443       CALL histwrite_phy(o_longitude, longitude_deg)
     444       CALL histwrite_phy(o_latitude, latitude_deg)
     445#endif
     446
    405447!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    406448! Simulateur AIRS
     
    10101052!This is warranted by treating INCA aerosols as offline aerosols
    10111053       IF (new_aod .and. (.not. aerosol_couple)) THEN
    1012 !       IF (new_aod) THEN
    10131054          IF (flag_aerosol.GT.0) THEN
    10141055             CALL histwrite_phy(o_od550aer, od550aer)
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/physiq_mod.F90

    r3611 r3629  
    223223    use FLOTT_GWD_rando_m, only: FLOTT_GWD_rando
    224224    use ACAMA_GWD_rando_m, only: ACAMA_GWD_rando
    225     USE vertical_layers_mod, only : Ahyb, Bhyb
     225    USE VERTICAL_LAYERS_MOD, ONLY: aps,bps, ap, bp
     226
     227
    226228    IMPLICIT none
    227229    !>======================================================================
     
    44334435            pphis, &
    44344436            zx_rh, &
    4435             Ahyb, Bhyb)
     4437            aps, bps, ap, bp)
    44364438
    44374439       CALL VTe(VTinca)
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/vertical_layers_mod.F90

    r2907 r3629  
    99   REAL,SAVE,ALLOCATABLE :: bp(:) ! hybrid (sigma contribution) coordinate
    1010                                  ! at layer interfaces (Pa)
     11   REAL,SAVE,ALLOCATABLE :: aps(:) ! hybrid (pressure contribution) coordinate
     12                                   ! at mid-layer (Pa)
     13   REAL,SAVE,ALLOCATABLE :: bps(:) ! hybrid (sigma contribution) coordinate
     14                                   ! at mid-layer
    1115   REAL,SAVE,ALLOCATABLE :: presnivs(:) ! reference pressure at mid-layer (Pa),
    1216                                        ! based on preff, ap and bp
     
    1418                                         ! based on preff and scaleheight
    1519   
    16 !$OMP THREADPRIVATE(preff,scaleheight,ap,bp,presnivs,pseudoalt)
    17    REAL, SAVE, ALLOCATABLE :: Ahyb(:), Bhyb(:)
    18 !$OMP THREADPRIVATE(Ahyb, Bhyb)
     20!$OMP THREADPRIVATE(preff,scaleheight,ap,bp,aps,bps,presnivs,pseudoalt)
     21
    1922
    2023CONTAINS
    2124
    2225  SUBROUTINE init_vertical_layers(nlayer,preff_,scaleheight_,ap_,bp_,&
    23                                  presnivs_, pseudoalt_)
     26                                 aps_,bps_,presnivs_, pseudoalt_)
    2427    IMPLICIT NONE
    2528    INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
     
    2831    REAL,INTENT(IN)    :: ap_(nlayer+1) ! hybrid coordinate at interfaces
    2932    REAL,INTENT(IN)    :: bp_(nlayer+1) ! hybrid coordinate at interfaces
     33    REAL,INTENT(IN)    :: aps_(nlayer) ! hybrid coordinate at mid-layer
     34    REAL,INTENT(IN)    :: bps_(nlayer) ! hybrid coordinate at mid-layer
    3035    REAL,INTENT(IN)    :: presnivs_(nlayer) ! Appproximative pressure of atm. layers (Pa)
    3136    REAL,INTENT(IN)    :: pseudoalt_(nlayer) ! pseudo-altitude of atm. layers (km)
     
    3338    ALLOCATE(ap(nlayer+1))
    3439    ALLOCATE(bp(nlayer+1))
     40    ALLOCATE(aps(nlayer))
     41    ALLOCATE(bps(nlayer))
    3542    ALLOCATE(presnivs(nlayer))
    3643    ALLOCATE(pseudoalt(nlayer))
    37     ALLOCATE(Ahyb(nlayer))
    38     ALLOCATE(Bhyb(nlayer))
    39 
    40 
     44 
    4145    preff = preff_
    4246    scaleheight=scaleheight_
    4347    ap(:) = ap_(:)
    4448    bp(:) = bp_(:)
     49    aps(:) = aps_(:)
     50    bps(:) = bps_(:)
    4551    presnivs(:) = presnivs_(:)
    4652    pseudoalt(:) = pseudoalt_(:)
Note: See TracChangeset for help on using the changeset viewer.