Changeset 1825 for LMDZ5/trunk


Ignore:
Timestamp:
Aug 2, 2013, 4:36:53 PM (11 years ago)
Author:
Ehouarn Millour
Message:

Première étape de l'implémentation de XIOS. Modifications isolées dans des flags CPP_XIOS. Sorties opérationnelles (sauf stations et régionalisation) en modes séquentiel et omp, pas mpi.
UG
...........................................
First step of the XIOS implementation. Modifications are confined into CPP_XIOS flags. Output is operationnal (except for stations and regionalization) in sequential and omp modes (not mpi).
UG

Location:
LMDZ5/trunk/libf
Files:
1 added
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/abort_gcm.F

    r1425 r1825  
    1212      USE ioipsl_getincom
    1313#endif
     14
     15#ifdef CPP_XIOS
     16    ! ug Pour les sorties XIOS
     17      USE wxios
     18#endif
     19
    1420#include "iniprint.h"
    1521 
     
    2733
    2834      write(lunout,*) 'in abort_gcm'
     35
     36#ifdef CPP_XIOS
     37    !Fermeture propre de XIOS
     38      CALL wxios_close()
     39#endif
     40
    2941#ifdef CPP_IOIPSL
    3042      call histclo
  • LMDZ5/trunk/libf/dyn3d/gcm.F

    r1785 r1825  
    1111! if not using IOIPSL, we still need to use (a local version of) getin
    1212      USE ioipsl_getincom
     13#endif
     14
     15
     16#ifdef CPP_XIOS
     17    ! ug Pour les sorties XIOS
     18        USE wxios
    1319#endif
    1420
     
    179185!      CALL defrun( 99, .TRUE. , clesphy0 )
    180186!#endif
     187
     188!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     189! Initialisation de XIOS
     190!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     191
     192#ifdef CPP_XIOS
     193        CALL wxios_init("LMDZ")
     194#endif
     195
    181196
    182197!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  • LMDZ5/trunk/libf/dyn3dpar/gcm.F

    r1823 r1825  
    88#ifdef CPP_IOIPSL
    99      USE IOIPSL
     10#endif
     11
     12
     13#ifdef CPP_XIOS
     14    ! ug Pour les sorties XIOS
     15        USE wxios
    1016#endif
    1117
     
    212218      call InitComgeomphy
    213219c$OMP END PARALLEL
     220#endif
     221
     222!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     223! Initialisation de XIOS
     224!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     225
     226#ifdef CPP_XIOS
     227        CALL wxios_init("LMDZ")
    214228#endif
    215229
  • LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F

    r1823 r1825  
    2222       USE control_mod
    2323
     24#ifdef CPP_XIOS
     25    ! ug Pour les sorties XIOS
     26        USE wxios
     27#endif
    2428      IMPLICIT NONE
    2529
     
    13691373
    13701374c$OMP MASTER
     1375
     1376#ifdef CPP_XIOS
     1377    !Fermeture propre de XIOS
     1378      CALL wxios_close()
     1379#endif
    13711380              call fin_getparam
    13721381              call finalize_parallel
  • LMDZ5/trunk/libf/phylmd/iophy.F90

    r1821 r1825  
    55
    66  USE phys_output_var_mod
     7
     8#ifdef CPP_XIOS
     9  USE wxios
     10#endif
    711
    812! abd  REAL,private,allocatable,DIMENSION(:),save :: io_lat
     
    2226
    2327  INTERFACE histbeg_phy_all
    24     MODULE PROCEDURE histbeg_phy,histbeg_phy_points
     28    MODULE PROCEDURE histbeg_phy,histbeg_phyxios,histbeg_phy_points
    2529  END INTERFACE
    2630
     
    4044  USE mod_grid_phy_lmdz
    4145  USE ioipsl
     46 
    4247  IMPLICIT NONE
    4348  INCLUDE 'dimensions.h'   
     
    8994    CALL flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
    9095                      'APPLE',phys_domain_id)
    91 
     96#ifdef CPP_XIOS
     97    !On initialise le domaine xios, maintenant que tout est connu:
     98    CALL wxios_domain_param("dom_glo", is_sequential, iim, jjm+1, io_lat, io_lon)
     99#endif
    92100!$OMP END MASTER
    93101     
     
    135143     
    136144  end SUBROUTINE init_iophy
     145
     146 SUBROUTINE histbeg_phyxios(name,itau0,zjulian,dtime,ffreq,lev,nhori,nid_day)
     147  USE dimphy
     148  USE mod_phys_lmdz_para
     149  use ioipsl
     150  use write_field
     151  IMPLICIT NONE
     152  include 'dimensions.h'
     153   
     154    character*(*), INTENT(IN) :: name
     155    integer, INTENT(IN) :: itau0
     156    REAL,INTENT(IN) :: zjulian
     157    REAL,INTENT(IN) :: dtime
     158    character(LEN=*), INTENT(IN) :: ffreq
     159    INTEGER,INTENT(IN) :: lev
     160    integer,intent(out) :: nhori
     161    integer,intent(out) :: nid_day
     162
     163!$OMP MASTER   
     164    if (is_sequential) then
     165      call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     166                   1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
     167    else
     168      call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     169                   1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
     170    endif
     171
     172#ifdef CPP_XIOS
     173    ! ug OMP en chantier...
     174    IF((.NOT. is_using_mpi) .OR. is_mpi_root) THEN
     175        ! ug Création du fichier
     176        CALL wxios_add_file(name, ffreq, lev)
     177    END IF
     178#endif
     179!$OMP END MASTER
     180 
     181  END SUBROUTINE histbeg_phyxios
    137182 
    138183  SUBROUTINE histbeg_phy(name,itau0,zjulian,dtime,nhori,nid_day)
     
    159204                   1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
    160205    endif
     206
    161207!$OMP END MASTER
    162208 
    163209  END SUBROUTINE histbeg_phy
     210
    164211
    165212  SUBROUTINE histbeg_phy_points(rlon,rlat,pim,tabij,ipt,jpt, &
     
    487534
    488535    IF(.NOT.clef_stations(iff)) THEN 
     536#ifdef CPP_XIOS
     537        CALL wxios_add_field_to_file(var%name, 2, nid_files(iff), phys_out_filenames(iff), &
     538        var%description, var%unit, var%flag(iff), typeecrit)
     539#endif
     540
    489541       IF ( var%flag(iff)<=lev_files(iff) ) THEN
    490542          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
     
    550602
    551603    IF(.NOT.clef_stations(iff)) THEN
     604#ifdef CPP_XIOS
     605        CALL wxios_add_field_to_file(var%name, 3, nid_files(iff), phys_out_filenames(iff), &
     606        var%description, var%unit, var%flag(iff), typeecrit)
     607#endif
     608
    552609       IF ( var%flag(iff)<=lev_files(iff) ) THEN
    553610          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
     
    734791
    735792#ifdef CPP_XIOS
    736 !  USE WXIOS
     793  USE wxios
    737794#endif
     795
    738796
    739797  IMPLICIT NONE
     
    794852                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,iim*jj_nb,index2d)
    795853#ifdef CPP_XIOS
    796 !                        IF (iff .EQ. 1) THEN
    797 !                              CALL wxios_write_2D(var%name, Field2d)
    798 !                        ENDIF
     854                        IF (iff == iff_beg) THEN
     855                              CALL wxios_write_2D(var%name, Field2d)
     856                        ENDIF
    799857#endif
    800858                  ELSE
     
    887945                        ALLOCATE(fieldok(iim*jj_nb,nlev))
    888946                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d,iim*jj_nb*nlev,index3d)
     947
    889948#ifdef CPP_XIOS
    890 !                        IF (iff .EQ. 1) THEN
    891 !                              CALL wxios_write_3D(var%name, Field3d(:,:,1:klev))
    892 !                        ENDIF
     949                        IF (iff == 1) THEN
     950                              CALL wxios_write_3D(var%name, Field3d(:,:,1:klev))
     951                        ENDIF
    893952#endif
    894953                       
  • LMDZ5/trunk/libf/phylmd/phys_output_mod.F90

    r1821 r1825  
    4242    USE aero_mod, only : naero_spc,name_aero
    4343    USE phys_output_ctrlout_mod
     44
     45#ifdef CPP_XIOS
     46    ! ug Pour les sorties XIOS
     47    USE wxios
     48#endif
    4449
    4550    IMPLICIT NONE
     
    98103    CHARACTER(LEN=3)                      :: ctetaSTD(nbteta)
    99104    REAL, DIMENSION(nfiles)               :: ecrit_files
    100     CHARACTER(LEN=20), DIMENSION(nfiles)  :: phys_out_filenames
    101105    INTEGER, DIMENSION(iim*jjmp1)         ::  ndex2d
    102106    INTEGER, DIMENSION(iim*jjmp1*klev)    :: ndex3d
     
    117121    REAL, DIMENSION(nfiles), SAVE     :: phys_out_latmin        = (/    -90.,    -90.,    -90.,     -90.,    -90.,    -90. /)
    118122    REAL, DIMENSION(nfiles), SAVE     :: phys_out_latmax        = (/     90.,     90.,     90.,     90.,     90.,     90. /)
     123
     124#ifdef CPP_XIOS
     125    ! ug Variables utilisées pour récupérer le calendrier pour xios
     126    INTEGER :: x_an, x_mois, x_jour
     127    REAL :: x_heure
     128#endif
    119129
    120130    WRITE(lunout,*) 'Debut phys_output_mod.F90'
     
    209219    WRITE(lunout,*)'phys_out_filelevels=',lev_files
    210220
     221#ifdef CPP_XIOS
     222    ! ug Réglage du calendrier xios
     223    !Temps julian => an, mois, jour, heure
     224    CALL ymds2ju(annee_ref, 1, day_ref, 0.0, zjulian)
     225    CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
     226    CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure)
     227#endif
     228
    211229!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    212230    ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
     
    257275!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    258276          IF (phys_out_regfkey(iff)) then
    259 
    260277             imin_ins=1
    261278             imax_ins=iim
     
    297314                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
    298315          else
    299              CALL histbeg_phy(phys_out_filenames(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
     316             CALL histbeg_phy_all(phys_out_filenames(iff),itau_phy,zjulian,&
     317                 dtime,chtimestep(iff),lev_files(iff),nhorim(iff),nid_files(iff))
    300318          endif
    301319
     
    329347          !                 1,preff,nvertp0(iff))
    330348
     349#ifdef CPP_XIOS
     350    ! ug déclaration des axes verticaux de chaque fichier:
     351    CALL wxios_add_vaxis("presnivs", nid_files(iff), levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
     352    CALL wxios_add_vaxis("Ahyb", nid_files(iff), levmax(iff) - levmin(iff) + 1, Ahyb)
     353    CALL wxios_add_vaxis("Bhyb", nid_files(iff), levmax(iff) - levmin(iff) + 1, Bhyb)
     354    CALL wxios_add_vaxis("Ahyb", nid_files(iff), levmax(iff) - levmin(iff) + 1, Alt)
     355#endif
    331356
    332357      IF (nqtot>=3) THEN
  • LMDZ5/trunk/libf/phylmd/phys_output_var_mod.F90

    r1807 r1825  
    4141      CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: type_ecri_files, phys_out_filetypes
    4242!$OMP THREADPRIVATE(type_ecri_files, phys_out_filetypes)
     43    CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: phys_out_filenames
     44!$OMP THREADPRIVATE(phys_out_filenames)
    4345
    4446 ! swaero_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
  • LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90

    r1821 r1825  
    3939    USE write_field_phy
    4040    USE iophy
     41    USE mod_phys_lmdz_para
     42
     43#ifdef CPP_XIOS
     44    ! ug Pour les sorties XIOS
     45        USE wxios
     46    USE xios
     47#endif
    4148
    4249    IMPLICIT NONE
     
    8087     ! On le donne à iophy pour que les histwrite y aient accès:
    8188     CALL set_itau_iophy(itau_w)
     89
     90    ! ug OMP en chantier...
     91    !IF(is_using_mpi .AND. .NOT. is_mpi_root) THEN
     92       ! vars_defined=.TRUE.
     93    !END IF
     94
    8295    IF(.NOT.vars_defined) THEN
    8396        iinitend = 2
     
    88101! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
    89102DO iinit=1, iinitend
     103#ifdef CPP_XIOS
     104IF (vars_defined) THEN
     105     CALL wxios_update_calendar(itau_w)
     106END IF
     107#endif
    90108! On procède à l'écriture ou à la définition des nombreuses variables:
    91109!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    9931011                ENDIF ! clef_files
    9941012            ENDDO !  iff
     1013#ifdef CPP_XIOS
     1014            !On finalise l'initialisation:
     1015            CALL wxios_closedef()
     1016#endif
    9951017!$OMP END MASTER
    9961018!$OMP BARRIER
Note: See TracChangeset for help on using the changeset viewer.