Changeset 5310 for LMDZ6


Ignore:
Timestamp:
Nov 1, 2024, 1:05:47 PM (8 weeks ago)
Author:
abarral
Message:

unify abort_gcm
rename wxios -> wxios_mod

Location:
LMDZ6/trunk/libf
Files:
1 added
1 deleted
26 edited
2 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/gcm.f90

    r5285 r5310  
    99  USE comdissnew_mod_h
    1010  USE IOIPSL
    11   USE wxios  ! ug Pour les sorties XIOS
     11  use wxios_mod  ! ug Pour les sorties XIOS
    1212  USE filtreg_mod
    1313  USE infotrac, ONLY: nqtot, init_infotrac
  • LMDZ6/trunk/libf/dyn3d_common/abort_gcm_NOMODULE.f90

    r5309 r5310  
    1 !
    2 ! $Id: abort_gcm.F 1747 2013-04-23 14:06:30Z lguez $
    3 !
    4 !
    5 !
     1! /!\ We can't put this in a module right away with FCM1, as this creates a circular dependency e.g. with wxios through iniprint_mod
     2
    63SUBROUTINE abort_gcm(modname, message, ierr)
    7 
    8   USE iniprint_mod_h
    9   USE IOIPSL
    10 
    11   USE parallel_lmdz
    12 
    13   !
    144  ! Stops the simulation cleanly, closing files and printing various
    155  ! comments
    16   !
     6
    177  !  Input: modname = name of calling program
    188  !     message = stuff to print
    199  !     ierr    = severity of situation ( = 0 normal )
    2010
    21   character(len=*), intent(in):: modname
    22   integer :: ierr, ierror_mpi
    23   character(len=*), intent(in):: message
     11  USE IOIPSL, ONLY: histclo, restclo, getin_dump
     12  USE wxios_mod, ONLY: using_xios, wxios_close
     13  USE mod_phys_lmdz_mpi_data, ONLY: mpi_rank
     14  USE lmdz_mpi, ONLY: using_mpi
     15  USE mod_const_mpi, ONLY: comm_lmdz
     16  USE iniprint_mod_h, ONLY: lunout, prt_level
     17  IMPLICIT NONE
    2418
    25   write(lunout,*) 'in abort_gcm'
    26 !$OMP MASTER
    27   call histclo
    28   call restclo
    29   if (MPI_rank .eq. 0) then
    30      call getin_dump
    31   endif
    32 !$OMP END MASTER
    33   ! call histclo(2)
    34   ! call histclo(3)
    35   ! call histclo(4)
    36   ! call histclo(5)
    37   write(lunout,*) 'Stopping in ', modname
    38   write(lunout,*) 'Reason = ',message
    39   if (ierr .eq. 0) then
    40     write(lunout,*) 'Everything is cool'
    41   else
    42     write(lunout,*) 'Houston, we have a problem, ierr = ', ierr
     19  CHARACTER(LEN = *), INTENT(IN) :: modname
     20  INTEGER, INTENT(IN) :: ierr
     21  CHARACTER(LEN = *), INTENT(IN) :: message
    4322
    44     if (using_mpi) THEN
    45 !$OMP CRITICAL (MPI_ABORT_GCM)
    46       call MPI_ABORT(COMM_LMDZ, 1, ierror_mpi)
    47 !$OMP END CRITICAL (MPI_ABORT_GCM)
    48     else
    49      stop 1
    50     endif
     23  INTEGER :: ierror_mpi
    5124
    52   endif
     25  WRITE(lunout, *) 'in abort_gcm'
     26
     27  IF (using_xios) THEN !Fermeture propre de XIOS
     28    CALL wxios_close()
     29  ENDIF
     30
     31  !$OMP MASTER
     32  CALL histclo
     33  CALL restclo
     34  IF (mpi_rank == 0) THEN
     35    CALL getin_dump
     36  ENDIF
     37  !$OMP END MASTER
     38  WRITE(lunout, *) 'Stopping in ', modname
     39  WRITE(lunout, *) 'Reason = ', message
     40  IF (ierr == 0) THEN
     41    WRITE(lunout, *) 'Everything is cool'
     42    IF (.NOT. using_mpi) THEN
     43      STOP
     44    END IF
     45  ELSE
     46    WRITE(lunout, *) 'Houston, we have a problem, ierr = ', ierr
     47
     48    IF (using_mpi) THEN
     49      !$OMP CRITICAL (MPI_ABORT_GCM)
     50      CALL MPI_ABORT(comm_lmdz, 1, ierror_mpi)
     51      !$OMP END CRITICAL (MPI_ABORT_GCM)
     52    ELSE
     53      STOP 1
     54    END IF
     55  END IF
    5356END SUBROUTINE abort_gcm
  • LMDZ6/trunk/libf/dyn3dmem/mod_const_mpi.F90

    r5267 r5310  
    1919    USE mod_prism
    2020#endif
    21     USE wxios, only: wxios_init, using_xios
     21    use wxios_mod, only: wxios_init, using_xios
    2222    IMPLICIT NONE
    2323
     
    5757  SUBROUTINE Init_mpi
    5858    USE lmdz_mpi
    59     USE wxios, only: wxios_init, using_xios
     59    use wxios_mod, only: wxios_init, using_xios
    6060
    6161  IMPLICIT NONE
  • LMDZ6/trunk/libf/dyn3dmem/mod_xios_dyn3dmem.f90

    r5285 r5310  
    1616
    1717     USE lmdz_xios
    18      USE wxios, ONLY : g_comm
     18     use wxios_mod, ONLY : g_comm
    1919     CHARACTER(len=100), SAVE :: dyn3d_ctx_name = "LMDZDYN"
    2020     TYPE(xios_context), SAVE :: dyn3d_ctx_handle
  • LMDZ6/trunk/libf/dyn3dmem/parallel_lmdz.F90

    r5285 r5310  
    391391    USE lmdz_mpi
    392392    ! ug Pour les sorties XIOS
    393         USE wxios
     393        use wxios_mod
    394394    USE control_mod, only : ok_dyn_xios
    395395    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
  • LMDZ6/trunk/libf/misc/wxios_mod.F90

    r5309 r5310  
    11! $Id$
    22
    3 MODULE wxios
     3MODULE wxios_mod
    44    USE lmdz_xios
    55
     
    783783         CALL xios_finalize()
    784784     END SUBROUTINE wxios_close
    785 END MODULE wxios
    786 
     785END MODULE wxios_mod
     786
  • LMDZ6/trunk/libf/phydev/iophy.F90

    r5267 r5310  
    3636  USE ioipsl, only: flio_dom_set
    3737
    38   use wxios, only: wxios_domain_param, using_xios
     38  use wxios_mod, only: wxios_domain_param, using_xios
    3939  implicit none
    4040    real,dimension(klon),intent(in) :: rlon
     
    172172 SUBROUTINE histbeg_phyxios(name,ffreq,lev)
    173173  USE mod_phys_lmdz_para, only: is_using_mpi, is_mpi_root
    174   use wxios, only: wxios_add_file
     174  use wxios_mod, only: wxios_add_file
    175175  IMPLICIT NONE
    176176   
  • LMDZ6/trunk/libf/phydev/physiq_mod.F90

    r4619 r5310  
    2424
    2525      USE lmdz_xios, ONLY: xios_update_calendar, using_xios
    26       USE wxios, only: wxios_add_vaxis, wxios_set_cal, wxios_closedef
     26      use wxios_mod, only: wxios_add_vaxis, wxios_set_cal, wxios_closedef
    2727      USE iophy, ONLY: histwrite_phy
    2828
  • LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r5296 r5310  
    392392    ! ug Pour les sorties XIOS
    393393    USE lmdz_xios, ONLY: xios_update_calendar, using_xios
    394     USE wxios, ONLY: wxios_closedef, missing_val_xios => missing_val
     394    use wxios_mod, ONLY: wxios_closedef, missing_val_xios => missing_val
    395395    USE phys_cal_mod, ONLY : mth_len
    396396
  • LMDZ6/trunk/libf/phylmd/cosp/cosp_output_mod.F90

    r4619 r5310  
    236236  USE print_control_mod, ONLY: lunout
    237237  ! ug Pour les sorties XIOS
    238   USE wxios
     238  use wxios_mod
    239239
    240240  IMPLICIT NONE
     
    260260!!! Variables d'entree
    261261
    262   ! ug Variables utilisées pour récupérer le calendrier pour xios
     262  ! ug Variables utilis�es pour r�cup�rer le calendrier pour xios
    263263  INTEGER :: x_an, x_mois, x_jour
    264264  REAL :: x_heure
  • LMDZ6/trunk/libf/phylmd/cosp/cosp_output_write_mod.F90

    r5282 r5310  
    2626    USE time_phylmdz_mod, ONLY: itau_phy, start_time, day_step_phy
    2727    USE print_control_mod, ONLY: lunout,prt_level
    28     USE wxios, only: wxios_closedef
     28    use wxios_mod, only: wxios_closedef
    2929    USE lmdz_xios, only: xios_update_calendar, xios_field_is_active, using_xios
    3030  IMPLICIT NONE 
     
    445445    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    446446    USE print_control_mod, ONLY: lunout,prt_level
    447     USE wxios
     447    use wxios_mod
    448448
    449449    IMPLICIT NONE
     
    506506    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    507507    USE print_control_mod, ONLY: lunout,prt_level
    508     USE wxios
     508    use wxios_mod
    509509
    510510    IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/cospv2/lmdz_cosp_output_mod.F90

    r4619 r5310  
    327327  USE print_control_mod, ONLY: lunout
    328328  ! ug Pour les sorties XIOS
    329   USE wxios
     329  use wxios_mod
    330330
    331331  IMPLICIT NONE
     
    347347!!! Variables d'entree
    348348
    349   ! ug Variables utilisées pour récupérer le calendrier pour xios
     349  ! ug Variables utilis�es pour r�cup�rer le calendrier pour xios
    350350  INTEGER :: x_an, x_mois, x_jour
    351351  REAL :: x_heure
  • LMDZ6/trunk/libf/phylmd/cospv2/lmdz_cosp_output_write_mod.f90

    r5282 r5310  
    4141  use mod_cosp,   only: cosp_outputs
    4242
    43     USE wxios, only: wxios_closedef
     43    use wxios_mod, only: wxios_closedef
    4444    USE lmdz_xios, only: xios_update_calendar, xios_field_is_active
    4545  IMPLICIT NONE 
     
    658658    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    659659    USE print_control_mod, ONLY: lunout,prt_level
    660   USE wxios
     660  use wxios_mod
    661661
    662662    IMPLICIT NONE
     
    712712    USE print_control_mod, ONLY: lunout,prt_level
    713713
    714   USE wxios
     714  use wxios_mod
    715715
    716716
  • LMDZ6/trunk/libf/phylmd/dyn1d/1DUTILS.h

    r5302 r5310  
    984984      END
    985985
    986 
    987 
    988       SUBROUTINE abort_gcm(modname, message, ierr)
    989 
    990       USE IOIPSL
    991 !
    992 ! Stops the simulation cleanly, closing files and printing various
    993 ! comments
    994 !
    995 !  Input: modname = name of calling program
    996 !         message = stuff to print
    997 !         ierr    = severity of situation ( = 0 normal )
    998 
    999       character(len=*) modname
    1000       integer ierr
    1001       character(len=*) message
    1002 
    1003       write(*,*) 'in abort_gcm'
    1004       call histclo
    1005 !     call histclo(2)
    1006 !     call histclo(3)
    1007 !     call histclo(4)
    1008 !     call histclo(5)
    1009       write(*,*) 'out of histclo'
    1010       write(*,*) 'Stopping in ', modname
    1011       write(*,*) 'Reason = ',message
    1012       call getin_dump
    1013 !
    1014       if (ierr .eq. 0) then
    1015         write(*,*) 'Everything is cool'
    1016       else
    1017         write(*,*) 'Houston, we have a problem ', ierr
    1018       endif
    1019       STOP
    1020       END
    1021986      REAL FUNCTION fq_sat(kelvin, millibar)
    1022987!
  • LMDZ6/trunk/libf/phylmd/dyn1d/replay1d.f90

    r5271 r5310  
    9494
    9595!=======================================================================
    96       SUBROUTINE abort_gcm(modname, message, ierr)
    97       USE IOIPSL
    98 ! Stops the simulation cleanly, closing files and printing various
    99 ! comments
    100 !=======================================================================
    101 !
    102 !  Input: modname = name of calling program
    103 !         message = stuff to print
    104 !         ierr    = severity of situation ( = 0 normal )
    105  
    106       character(len=*) modname
    107       integer ierr
    108       character(len=*) message
    109  
    110       write(*,*) 'in abort_gcm'
    111       call histclo
    112       write(*,*) 'out of histclo'
    113       write(*,*) 'Stopping in ', modname
    114       write(*,*) 'Reason = ',message
    115       call getin_dump
    116 !
    117       if (ierr .eq. 0) then
    118         write(*,*) 'Everything is cool'
    119       else
    120         write(*,*) 'Houston, we have a problem ', ierr
    121       endif
    122       STOP
    123       END
    124 
    125 !=======================================================================
    12696      SUBROUTINE gr_dyn_fi(nfield,im,jm,ngrid,pdyn,pfi)
    12797      IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/iophy.F90

    r5282 r5310  
    4545    USE ioipsl, ONLY: flio_dom_set
    4646
    47   use wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init, using_xios
     47  use wxios_mod, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init, using_xios
    4848    IMPLICIT NONE
    4949    REAL,DIMENSION(klon),INTENT(IN) :: rlon
     
    213213  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    214214  USE ioipsl, ONLY: histbeg
    215   USE wxios, ONLY: wxios_add_file, using_xios
     215  use wxios_mod, ONLY: wxios_add_file, using_xios
    216216  IMPLICIT NONE
    217217   
     
    588588    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    589589    USE aero_mod, ONLY : naero_tot, name_aero_tau
    590     USE wxios, ONLY: wxios_add_field_to_file, using_xios
     590    use wxios_mod, ONLY: wxios_add_field_to_file, using_xios
    591591    USE print_control_mod, ONLY: prt_level,lunout
    592592    USE clesphys_mod_h
     
    703703    USE print_control_mod, ONLY: prt_level,lunout
    704704    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    705     USE wxios, ONLY: wxios_add_field_to_file, using_xios
     705    use wxios_mod, ONLY: wxios_add_field_to_file, using_xios
    706706    USE print_control_mod, ONLY: prt_level,lunout
    707707    USE clesphys_mod_h
  • LMDZ6/trunk/libf/phylmd/moy_undefSTD.f90

    r5282 r5310  
    77  USE dimphy
    88  USE phys_state_var_mod
    9   USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     9  use wxios_mod, ONLY: missing_val_xios => missing_val, using_xios
    1010
    1111  USE phys_cal_mod, ONLY: mth_len
  • LMDZ6/trunk/libf/phylmd/oasis.F90

    r5251 r5310  
    114114    USE surface_data, ONLY : version_ocean
    115115    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    116     USE wxios, ONLY : wxios_context_init
     116    use wxios_mod, ONLY : wxios_context_init
    117117    USE chemistry_cycle_mod, ONLY : dms_cycle_cpl, n2o_cycle_cpl
    118118    USE lmdz_xios 
  • LMDZ6/trunk/libf/phylmd/pbl_surface_mod.F90

    r5305 r5310  
    417417    use phys_output_var_mod, only: tkt, tks, taur, sss
    418418    use lmdz_blowing_snow_ini, only : zeta_bs
    419     USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     419    use wxios_mod, ONLY: missing_val_xios => missing_val, using_xios
    420420    USE netcdf, only: missing_val_netcdf => nf90_fill_real
    421421    USE dimsoil_mod_h, ONLY: nsoilmx
  • LMDZ6/trunk/libf/phylmd/phyetat0_mod.f90

    r5296 r5310  
    4141  USE ocean_slab_mod,   ONLY: nslay, tslab, seaice, tice, ocean_slab_init
    4242  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
    43   USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     43  use wxios_mod, ONLY: missing_val_xios => missing_val, using_xios
    4444  use netcdf, only: missing_val_netcdf => nf90_fill_real
    4545  use config_ocean_skin_m, only: activate_ocean_skin
  • LMDZ6/trunk/libf/phylmd/phys_output_mod.F90

    r5285 r5310  
    4848    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
    4949    ! ug Pour les sorties XIOS
    50     USE wxios
     50    use wxios_mod
    5151   USE infotrac_phy, ONLY: nbtr_bin
    5252#ifdef ISO
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r5296 r5310  
    464464    ! ug Pour les sorties XIOS
    465465    USE lmdz_xios
    466     USE wxios, ONLY: wxios_closedef, missing_val_xios=>missing_val, wxios_set_context
     466    use wxios_mod, ONLY: wxios_closedef, missing_val_xios=>missing_val, wxios_set_context
    467467    USE phys_cal_mod, ONLY : mth_len
    468468
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r5305 r5310  
    7474    USE vampir
    7575    USE write_field_phy
    76     USE wxios, ONLY: g_ctx, wxios_set_context
     76    use wxios_mod, ONLY: g_ctx, wxios_set_context
    7777    USE lmdz_lscp, ONLY : lscp
    7878    USE lmdz_call_cloud_optics_prop, ONLY : call_cloud_optics_prop
     
    128128    USE lmdz_xios, ONLY: xios_get_field_attr, xios_field_is_active, xios_context
    129129    USE lmdz_xios, ONLY: xios_set_current_context
    130     USE wxios, ONLY: missing_val, using_xios
     130    use wxios_mod, ONLY: missing_val, using_xios
    131131
    132132#ifndef CPP_XIOS
  • LMDZ6/trunk/libf/phylmd/plevel.f90

    r5268 r5310  
    1010  USE dimphy
    1111  USE phys_state_var_mod, ONLY: missing_val_nf90
    12   USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     12  use wxios_mod, ONLY: missing_val_xios => missing_val, using_xios
    1313  IMPLICIT NONE
    1414
  • LMDZ6/trunk/libf/phylmd/plevel_new.f90

    r5268 r5310  
    1111  USE dimphy
    1212  USE phys_state_var_mod, ONLY: missing_val_nf90
    13   USE wxios, ONLY: missing_val_xios=>missing_val, using_xios
     13  use wxios_mod, ONLY: missing_val_xios=>missing_val, using_xios
    1414
    1515  IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/undefSTD.f90

    r5296 r5310  
    77  USE dimphy
    88  USE phys_state_var_mod
    9   USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     9  use wxios_mod, ONLY: missing_val_xios => missing_val, using_xios
    1010
    1111  IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90

    r5296 r5310  
    4848  USE ocean_slab_mod,   ONLY: nslay, tslab, seaice, tice, ocean_slab_init
    4949  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
    50   USE wxios, ONLY: missing_val_xios => missing_val, using_xios
     50  use wxios_mod, ONLY: missing_val_xios => missing_val, using_xios
    5151  use netcdf, only: missing_val_netcdf => nf90_fill_real
    5252  use config_ocean_skin_m, only: activate_ocean_skin
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r5305 r5310  
    7474    USE vampir
    7575    USE write_field_phy
    76     USE wxios, ONLY: g_ctx, wxios_set_context
     76    use wxios_mod, ONLY: g_ctx, wxios_set_context
    7777    USE lmdz_lscp, ONLY : lscp
    7878    USE lmdz_call_cloud_optics_prop, ONLY : call_cloud_optics_prop
     
    131131    USE lmdz_xios, ONLY: xios_get_field_attr, xios_field_is_active, xios_context
    132132    USE lmdz_xios, ONLY: xios_set_current_context
    133     USE wxios, ONLY: missing_val, using_xios
     133    use wxios_mod, ONLY: missing_val, using_xios
    134134
    135135#ifndef CPP_XIOS
Note: See TracChangeset for help on using the changeset viewer.