Changeset 4028


Ignore:
Timestamp:
Jul 31, 2017, 3:03:54 PM (7 years ago)
Author:
millour
Message:

Rearrange ICOSAGCM/Physics interface so that multiple different LMDZ physics packages may be used.
So far only interfaces with 'lmd' and 'dev' physics are handled.
Added a 'DEV_PHYSICS' directory with sample def and xml files to test correct integration with 'dev' physics.
EM

Location:
dynamico_lmdz/aquaplanet
Files:
28 added
9 edited
1 moved

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/ICOSA_LMDZ/bld.cfg

    r3991 r4028  
    1515dir::root            $PWD
    1616
    17 src::src        src
    18 search_src           false
     17# Do not scan source tree subdirectories
     18search_src           0
     19
     20# source code directories
     21src::src             src
     22src::phys            src/%PHYS
     23
    1924bld::lib icosa_lmdz
    2025bld::target libicosa_lmdz.a icosa_lmdz.exe
     
    3237bld::pp              false
    3338
     39# external dependencies to not track
    3440bld::excl_dep        use::netcdf
    3541bld::excl_dep        use::omp_lib
  • dynamico_lmdz/aquaplanet/ICOSA_LMDZ/clean

    r3840 r4028  
    88rm -rf ./lib
    99rm -rf ./bin
     10rm -rf ./.cache
    1011
    1112
  • dynamico_lmdz/aquaplanet/ICOSA_LMDZ/compile

    r3966 r4028  
    1 make_icosa_lmdz -debug -parallel mpi_omp -with_orchidee -arch X64_ADA -job 8
     1make_icosa_lmdz -debug -parallel mpi_omp -p lmd -with_orchidee -arch X64_ADA -arch_path ../ARCH -job 8
  • dynamico_lmdz/aquaplanet/ICOSA_LMDZ/make_icosa_lmdz

    r3991 r4028  
    2929      "-h") cat <<fin
    3030Usage :
    31 makegcm [options] -m arch exec
     31makegcm [options] -m arch -p phys  exec
    3232[-h]                       : help
    3333[-prod / -dev / -debug]    : compilation en mode production (default) / developpement / debug .
    3434[-nodeps]                  : do not build dependencies (XIOS, IOIPSL, LMDZ5, ICOSAGCM)
    3535 -arch nom_arch            : nom de l\'architecture cible
     36 -p phys                   : physics package (e.g. std , venus , ...)
     37[-p_opt "options"]         : additional options for physics package
    3638fin
    3739          exit;;
    3840
     41      "-p")
     42          phys=$2 ; shift ; shift ;;
     43     
     44      "-p_opt")
     45          phys_opt=$2 ; shift ; shift ;;
     46         
    3947      "-prod")
    4048          compil_mode="prod" ; shift ;;
     
    182190echo "%LD_FLAGS $LD_FLAGS" >> config.fcm
    183191echo "%CPP_KEY $CPP_KEY" >> config.fcm
     192echo "%PHYS phy$phys" >> config.fcm
    184193echo "%LIB $ICOSA_LIB">> config.fcm
    185194
     
    208217        lmdz_veget="orchidee2.0 -cpp ORCHIDEE_NOZ0H"
    209218    fi
    210 #    ./makelmdz_fcm gcm -$compil_mode -mem -parallel $parallel -nodyn -io xios -v $lmdz_veget -arch $arch -arch_path $arch_path -j $job $full_flag || exit 1
    211     ./makelmdz_fcm gcm -$compil_mode -mem -parallel $parallel -libphy -io xios -v $lmdz_veget -arch $arch -arch_path $arch_path -j $job $full_flag || exit 1
     219    ./makelmdz_fcm -p $phys $phys_opt -$compil_mode -mem -parallel $parallel -libphy -io xios -v $lmdz_veget -arch $arch -arch_path $arch_path -j $job $full_flag || exit 1
    212220    cd -
    213221
  • dynamico_lmdz/aquaplanet/ICOSA_LMDZ/src/phylmd/interface_icosa_lmdz.f90

    r4027 r4028  
    298298    aps(1:llm)=0.5*(ap(1:llm)+ap(2:llm+1))
    299299    bps(1:llm)=0.5*(bp(1:llm)+bp(2:llm+1))
    300     pseudoalt(:)=0
     300    pseudoalt(:)=-scaleheight*log(presnivs(:)/preff)
    301301    CALL init_vertical_layers(llm,preff,scaleheight,ap,bp,aps,bps,presnivs,pseudoalt)
    302302
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dynphy_lonlat/inigeomphy_mod.F90

    r3990 r4028  
    9494 
    9595  DO i=1,iim
    96    boundslon_reg(i,east)=rlonu(i)
    97    boundslon_reg(i,west)=rlonu(i+1)
     96   boundslon_reg(i,east)=rlonu(i+1)
     97   boundslon_reg(i,west)=rlonu(i)
    9898  ENDDO
    9999
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/dynphy_lonlat/phydev/iniphysiq_mod.F90

    r3990 r4028  
    7171  CALL inifis(prad,pg,pr,pcpp)
    7272 
    73   ! Initialize dimphy module
    74   CALL Init_dimphy(klon_omp,nlayer)
    75 
    7673  ! Initialize tracer names, numbers, etc. for physics
    7774  CALL init_infotrac_phy(nqtot,type_trac)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phydev/inifis_mod.F90

    r3990 r4028  
    66  SUBROUTINE inifis(prad, pg, pr, pcpp)
    77  ! Initialize some physical constants and settings
    8   USE print_control_mod, ONLY: init_print_control
     8  USE init_print_control_mod, ONLY: init_print_control
    99  USE comcstphy, ONLY: rradius, & ! planet radius (m)
    1010                       rr, & ! recuced gas constant: R/molar mass of atm
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phydev/iophy.F90

    r3990 r4028  
    1111  INTEGER, save :: npstn
    1212  INTEGER, allocatable, dimension(:), save :: nptabij
    13  
    1413
    1514#ifdef CPP_XIOS
     
    4544                                mpi_size, mpi_rank, klon_mpi, &
    4645                                is_sequential, is_south_pole_dyn
    47   USE mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, klon_glo
     46  USE mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, klon_glo, grid_type, unstructured
    4847  USE print_control_mod, ONLY: lunout, prt_level
    4948  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
     
    5251#endif
    5352#ifdef CPP_XIOS
    54   use wxios, only: wxios_domain_param
     53  use wxios, only: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init
    5554#endif
    5655  implicit none
     
    7170    integer :: data_ibegin,data_iend
    7271
    73     CALL gather(rlat,rlat_glo)
    74     CALL bcast(rlat_glo)
    75     CALL gather(rlon,rlon_glo)
    76     CALL bcast(rlon_glo)
    77    
    78 !$OMP MASTER 
    79     ALLOCATE(io_lat(nbp_lat))
    80     io_lat(1)=rlat_glo(1)
    81     io_lat(nbp_lat)=rlat_glo(klon_glo)
    82     IF ((nbp_lon*nbp_lat) > 1) then
    83       DO i=2,nbp_lat-1
    84         io_lat(i)=rlat_glo(2+(i-2)*nbp_lon)
    85       ENDDO
     72#ifdef CPP_XIOS
     73      CALL wxios_context_init
     74#endif
     75   
     76    IF (grid_type==unstructured) THEN
     77   
     78#ifdef CPP_XIOS
     79      CALL wxios_domain_param_unstructured("dom_glo")
     80#endif
     81   
     82    ELSE
     83
     84      CALL gather(rlat,rlat_glo)
     85      CALL bcast(rlat_glo)
     86      CALL gather(rlon,rlon_glo)
     87      CALL bcast(rlon_glo)
     88   
     89  !$OMP MASTER 
     90      ALLOCATE(io_lat(nbp_lat))
     91      io_lat(1)=rlat_glo(1)
     92      io_lat(nbp_lat)=rlat_glo(klon_glo)
     93      IF ((nbp_lon*nbp_lat) > 1) then
     94        DO i=2,nbp_lat-1
     95          io_lat(i)=rlat_glo(2+(i-2)*nbp_lon)
     96        ENDDO
     97      ENDIF
     98
     99      ALLOCATE(io_lon(nbp_lon))
     100      IF (klon_glo == 1) THEN
     101        io_lon(1)=rlon_glo(1)
     102      ELSE
     103        io_lon(1:nbp_lon)=rlon_glo(2:nbp_lon+1)
     104      ENDIF
     105   
     106  !! (I) dtnb   : total number of domains
     107  !! (I) dnb    : domain number
     108  !! (I) did(:) : distributed dimensions identifiers
     109  !!              (up to 5 dimensions are supported)
     110  !! (I) dsg(:) : total number of points for each dimension
     111  !! (I) dsl(:) : local number of points for each dimension
     112  !! (I) dpf(:) : position of first local point for each dimension
     113  !! (I) dpl(:) : position of last local point for each dimension
     114  !! (I) dhs(:) : start halo size for each dimension
     115  !! (I) dhe(:) : end halo size for each dimension
     116  !! (C) cdnm   : Model domain definition name.
     117  !!              The names actually supported are :
     118  !!              "BOX", "APPLE", "ORANGE".
     119  !!              These names are case insensitive.
     120
     121      ddid=(/ 1,2 /)
     122      dsg=(/ nbp_lon, nbp_lat /)
     123      dsl=(/ nbp_lon, jj_nb /)
     124      dpf=(/ 1,jj_begin /)
     125      dpl=(/ nbp_lon, jj_end /)
     126      dhs=(/ ii_begin-1,0 /)
     127      IF (mpi_rank==mpi_size-1) THEN
     128        dhe=(/0,0/)
     129      ELSE
     130        dhe=(/ nbp_lon-ii_end,0 /) 
     131      ENDIF
     132
     133#ifndef CPP_IOIPSL_NO_OUTPUT   
     134      CALL flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
     135                        'APPLE',phys_domain_id)
     136#endif
     137#ifdef CPP_XIOS
     138      ! Set values for the mask:
     139      IF (mpi_rank == 0) THEN
     140          data_ibegin = 0
     141      ELSE
     142          data_ibegin = ii_begin - 1
     143      END IF
     144
     145      IF (mpi_rank == mpi_size-1) THEN
     146          data_iend = nbp_lon
     147      ELSE
     148          data_iend = ii_end + 1
     149      END IF
     150
     151      if (prt_level>=10) then
     152        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
     153        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
     154        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
     155        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
     156        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole_dyn=",is_south_pole_dyn
     157      endif
     158#endif
     159
     160!$OMP END MASTER
     161
     162#ifdef CPP_XIOS
     163      ! Initialize the XIOS domain coreesponding to this process:
     164   
     165        CALL wxios_domain_param("dom_glo")
     166#endif
     167
    86168    ENDIF
    87 
    88     ALLOCATE(io_lon(nbp_lon))
    89     IF ((nbp_lon*nbp_lat) > 1) THEN
    90       io_lon(:)=rlon_glo(2:nbp_lon+1)
    91     ELSE
    92       io_lon(1)=rlon_glo(1)
    93     ENDIF
    94 !! (I) dtnb   : total number of domains
    95 !! (I) dnb    : domain number
    96 !! (I) did(:) : distributed dimensions identifiers
    97 !!              (up to 5 dimensions are supported)
    98 !! (I) dsg(:) : total number of points for each dimension
    99 !! (I) dsl(:) : local number of points for each dimension
    100 !! (I) dpf(:) : position of first local point for each dimension
    101 !! (I) dpl(:) : position of last local point for each dimension
    102 !! (I) dhs(:) : start halo size for each dimension
    103 !! (I) dhe(:) : end halo size for each dimension
    104 !! (C) cdnm   : Model domain definition name.
    105 !!              The names actually supported are :
    106 !!              "BOX", "APPLE", "ORANGE".
    107 !!              These names are case insensitive.
    108     ddid=(/ 1,2 /)
    109     dsg=(/ nbp_lon, nbp_lat /)
    110     dsl=(/ nbp_lon, jj_nb /)
    111     dpf=(/ 1,jj_begin /)
    112     dpl=(/ nbp_lon, jj_end /)
    113     dhs=(/ ii_begin-1,0 /)
    114     if (mpi_rank==mpi_size-1) then
    115       dhe=(/0,0/)
    116     else
    117       dhe=(/ nbp_lon-ii_end,0 /) 
    118     endif
    119    
    120 #ifndef CPP_IOIPSL_NO_OUTPUT
    121     call flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
    122                       'APPLE',phys_domain_id)
    123 #endif
    124 #ifdef CPP_XIOS
    125     ! Set values for the mask:
    126     IF (mpi_rank == 0) THEN
    127         data_ibegin = 0
    128     ELSE
    129         data_ibegin = ii_begin - 1
    130     END IF
    131 
    132     IF (mpi_rank == mpi_size-1) THEN
    133         data_iend = nbp_lon
    134     ELSE
    135         data_iend = ii_end + 1
    136     END IF
    137 
    138     if (prt_level>=10) then
    139       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
    140       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
    141       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    142       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    143       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole=",is_south_pole_dyn
    144     endif
    145 
    146     ! Initialize the XIOS domain coreesponding to this process:
    147     CALL wxios_domain_param("dom_glo", is_sequential, nbp_lon, jj_nb, nbp_lon, nbp_lat, &
    148                             1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
    149                             klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
    150                             io_lat, io_lon,is_south_pole_dyn,mpi_rank)
    151 #endif
    152 !$OMP END MASTER
    153      
     169           
    154170  END SUBROUTINE init_iophy_new
    155171 
     
    223239                                jj_nb, klon_mpi
    224240  USE ioipsl, only: histwrite
    225   USE mod_grid_phy_lmdz, ONLY: nbp_lon
     241  USE mod_grid_phy_lmdz, ONLY: nbp_lon, grid_type, regular_lonlat, unstructured
    226242  implicit none
    227243   
     
    242258    CALL Gather_omp(field,buffer_omp)   
    243259!$OMP MASTER
    244     CALL grid1Dto2D_mpi(buffer_omp,Field2d)
     260    if (grid_type==regular_lonlat) CALL grid1Dto2D_mpi(buffer_omp,Field2d)
    245261    if(.NOT.lpoint) THEN
    246262     ALLOCATE(index2d(nbp_lon*jj_nb))
     
    282298                                jj_nb, klon_mpi
    283299  USE ioipsl, only: histwrite
    284   USE mod_grid_phy_lmdz, ONLY: nbp_lon
     300  USE mod_grid_phy_lmdz, ONLY: nbp_lon, grid_type, regular_lonlat, unstructured
    285301  implicit none
    286302   
     
    301317    CALL Gather_omp(field,buffer_omp)
    302318!$OMP MASTER
    303     CALL grid1Dto2D_mpi(buffer_omp,field3d)
     319    if (grid_type==regular_lonlat) CALL grid1Dto2D_mpi(buffer_omp,field3d)
    304320    if(.NOT.lpoint) THEN
    305321     ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
     
    346362  USE xios, only: xios_send_field
    347363  USE print_control_mod, ONLY: prt_level, lunout
    348   USE mod_grid_phy_lmdz, ONLY: nbp_lon
     364  USE mod_grid_phy_lmdz, ONLY: nbp_lon, grid_type, unstructured
    349365  IMPLICIT NONE
    350366
     
    360376   
    361377    CALL Gather_omp(field,buffer_omp)   
     378
    362379!$OMP MASTER
    363     CALL grid1Dto2D_mpi(buffer_omp,Field2d)
    364    
    365     CALL xios_send_field(field_name, Field2d)
     380    IF (grid_type==unstructured) THEN
     381      CALL xios_send_field(field_name, buffer_omp)
     382    ELSE
     383      CALL grid1Dto2D_mpi(buffer_omp,Field2d)   
     384      CALL xios_send_field(field_name, Field2d)
     385    ENDIF !of IF (grid_type==unstructured)
    366386!$OMP END MASTER   
    367387
     
    380400  USE xios, only: xios_send_field
    381401  USE print_control_mod, ONLY: prt_level,lunout
    382   USE mod_grid_phy_lmdz, ONLY: nbp_lon
     402  USE mod_grid_phy_lmdz, ONLY: nbp_lon, grid_type, unstructured
    383403
    384404  IMPLICIT NONE
     
    399419
    400420    CALL Gather_omp(field,buffer_omp)
     421
    401422!$OMP MASTER
    402     CALL grid1Dto2D_mpi(buffer_omp,field3d)
    403 
    404     CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
     423    IF (grid_type==unstructured) THEN
     424      CALL xios_send_field(field_name, buffer_omp(:,1:nlev))
     425    ELSE   
     426      CALL grid1Dto2D_mpi(buffer_omp,field3d)
     427      CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
     428    ENDIF !of IF (grid_type==unstructured)
    405429!$OMP END MASTER   
    406430
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phydev/physiq_mod.F90

    r3990 r4028  
    2222      USE phys_state_var_mod, only : phys_state_var_init
    2323      USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat
    24 
    25 #ifdef CPP_XIOS
    26       USE xios, ONLY: xios_update_calendar
     24      USE mod_phys_lmdz_omp_data, ONLY: is_omp_master
     25      USE write_field_phy, ONLY: writefield_phy
     26
     27#ifdef CPP_XIOS
     28      USE xios, ONLY: xios_update_calendar, xios_context_finalize
    2729      USE wxios, only: wxios_add_vaxis, wxios_set_cal, wxios_closedef
    2830      USE iophy, ONLY: histwrite_phy
     
    195197if (lafin) then
    196198  call phyredem("restartphy.nc")
     199#ifdef CPP_XIOS
     200  IF (is_omp_master) CALL xios_context_finalize
     201#endif
    197202endif
    198203
Note: See TracChangeset for help on using the changeset viewer.