Ignore:
Timestamp:
Oct 23, 2024, 5:34:46 PM (2 days ago)
Author:
abarral
Message:

Remove CPP_IOIPSL cpp keys uses

Location:
LMDZ6/trunk/libf/dyn3dmem
Files:
18 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3dmem/abort_gcm.F90

    r5246 r5267  
    66SUBROUTINE abort_gcm(modname, message, ierr)
    77
    8 #ifdef CPP_IOIPSL
    98  USE IOIPSL
    10 #else
    11   ! if not using IOIPSL, we still need to use (a local version of) getin_dump
    12   USE ioipsl_getincom
    13 #endif
     9
    1410  USE parallel_lmdz
    1511  INCLUDE "iniprint.h"
     
    2824
    2925  write(lunout,*) 'in abort_gcm'
    30 #ifdef CPP_IOIPSL
    3126!$OMP MASTER
    3227  call histclo
     
    3631  endif
    3732!$OMP END MASTER
    38 #endif
    3933  ! call histclo(2)
    4034  ! call histclo(3)
  • LMDZ6/trunk/libf/dyn3dmem/bilan_dyn_loc.F90

    r5246 r5267  
    1010  !             vQ..A=Cp T + L * ...
    1111
    12 #ifdef CPP_IOIPSL
    1312  USE IOIPSL
    14 #endif
    1513  USE parallel_lmdz
    1614  USE mod_hallo
     
    3028  !====================================================================
    3129  !
    32   !   Sous-programme consacre à des diagnostics dynamiques de base
     30  !   Sous-programme consacre des diagnostics dynamiques de base
    3331  !
    3432  !
     
    8886  real :: ww
    8987
    90   !   variables dynamiques intermédiaires
     88  !   variables dynamiques intermdiaires
    9189  REAL,SAVE,ALLOCATABLE :: vcont(:,:,:),ucont(:,:,:)
    9290  REAL,SAVE,ALLOCATABLE :: ang(:,:,:),unat(:,:,:)
     
    9694  REAL,SAVE,ALLOCATABLE :: bern(:,:,:)
    9795
    98   !   champ contenant les scalaires advectés.
     96  !   champ contenant les scalaires advects.
    9997  real,SAVE,ALLOCATABLE :: Q(:,:,:,:)
    10098
    101   !   champs cumulés
     99  !   champs cumuls
    102100  real,SAVE,ALLOCATABLE ::  ps_cum(:,:)
    103101  real,SAVE,ALLOCATABLE ::  masse_cum(:,:,:)
     
    370368  jje=jj_end
    371369
    372   !   énergie cinétique
     370  !   �nergie cin�tique
    373371   ! ucont(:,jjb:jje,:)=0
    374372
     
    382380  CALL enercin_loc(vcov,ucov,vcont,ucont,ecin)
    383381
    384   !   moment cinétique
     382  !   moment cintique
    385383!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    386384  do l=1,llm
     
    490488  enddo
    491489
    492   !    flux méridien
     490  !    flux mridien
    493491  !    -------------
    494492  do iQ=1,nQ
     
    642640
    643641  !=====================================================================
    644   !   Transport méridien
     642  !   Transport mridien
    645643  !=====================================================================
    646644
  • LMDZ6/trunk/libf/dyn3dmem/check_isotopes_loc.F90

    r5214 r5267  
    55                          ntiso, iH2O, nzone, tracers, isoName,  itZonIso
    66   USE iso_params_mod, ONLY: tnat_H216O, tnat_H217O, tnat_H218O, tnat_HDO, tnat_HTO
    7 #ifdef CPP_IOIPSL
    87   USE ioipsl,          ONLY: getin
    9 #else
    10    USE ioipsl_getincom, ONLY: getin
    11 #endif
    128   IMPLICIT NONE
    139   include "dimensions.h"
  • LMDZ6/trunk/libf/dyn3dmem/conf_gcm.F90

    r4996 r5267  
    55
    66  USE control_mod
    7 #ifdef CPP_IOIPSL
    87  USE IOIPSL
    9 #else
    10   ! if not using IOIPSL, we still need to use (a local version of) getin
    11   USE ioipsl_getincom
    12 #endif
     8
    139  USE misc_mod
    1410  USE mod_filtre_fft, ONLY: use_filtre_fft
     
    121117
    122118  !Config  Key  = prt_level
    123   !Config  Desc = niveau d'impressions de débogage
     119  !Config  Desc = niveau d'impressions de dbogage
    124120  !Config  Def  = 0
    125   !Config  Help = Niveau d'impression pour le débogage
     121  !Config  Help = Niveau d'impression pour le dbogage
    126122  !Config         (0 = minimum d'impression)
    127123  prt_level = 0
     
    921917
    922918     !Config  Key  = use_mpi_alloc
    923      !Config  Desc = Utilise un buffer MPI en m�moire globale
     919     !Config  Desc = Utilise un buffer MPI en mmoire globale
    924920     !Config  Def  = false
    925921     !Config  Help = permet d'activer l'utilisation d'un buffer MPI
    926      !Config         en m�moire globale a l'aide de la fonction MPI_ALLOC.
    927      !Config         Cela peut am�liorer la bande passante des transferts MPI
     922     !Config         en mmoire globale a l'aide de la fonction MPI_ALLOC.
     923     !Config         Cela peut amliorer la bande passante des transferts MPI
    928924     !Config         d'un facteur 2 
    929925     use_mpi_alloc=.FALSE.
     
    933929     !Config  Desc = activation de la version strato
    934930     !Config  Def  = .FALSE.
    935      !Config  Help = active la version stratosphérique de LMDZ de F. Lott
     931     !Config  Help = active la version stratosphrique de LMDZ de F. Lott
    936932
    937933     ok_strato=.FALSE.
  • LMDZ6/trunk/libf/dyn3dmem/dynetat0_loc.F90

    r5252 r5267  
    2020  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
    2121  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    22 #ifdef CPP_IOIPSL
    2322  USE IOIPSL,   ONLY: getin
    24 #else
    25   USE ioipsl_getincom, ONLY: getin
    26 #endif
    2723  USE iso_params_mod   ! tnat_* and alpha_ideal_*
    2824  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS
  • LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.F90

    r5084 r5267  
    44! Write the NetCDF restart file (initialization).
    55!-------------------------------------------------------------------------------
    6 #ifdef CPP_IOIPSL
    76  USE IOIPSL
    8 #endif
    97  USE parallel_lmdz
    108  USE mod_hallo
     
    5351  IF(mpi_rank/=0) RETURN
    5452
    55 #ifdef CPP_IOIPSL
    5653  CALL ymds2ju(annee_ref, 1, iday_end, 0.0, zjulian)
    5754  CALL ju2ymds(zjulian, yyears0, mmois0, jjour0, hours)
    58 #else
    59 ! set yyears0, mmois0, jjour0 to 0,1,1 (hours is not used)
    60   yyears0=0
    61   mmois0=1
    62   jjour0=1
    63 #endif       
     55
    6456
    6557  tab_cntrl(:)  = 0.
  • LMDZ6/trunk/libf/dyn3dmem/friction_loc.F90

    r5246 r5267  
    66  USE parallel_lmdz
    77  USE control_mod
    8 #ifdef CPP_IOIPSL
    98  USE IOIPSL
    10 #else
    11   ! if not using IOIPSL, we still need to use (a local version of) getin
    12   USE ioipsl_getincom
    13 #endif
     9
    1410  USE comconst_mod, ONLY: pi
    1511  IMPLICIT NONE
  • LMDZ6/trunk/libf/dyn3dmem/gcm.F90

    r5250 r5267  
    55PROGRAM gcm
    66
    7 #ifdef CPP_IOIPSL
    87  USE IOIPSL
    9 #endif
    108
    119  USE mod_const_mpi, ONLY: init_const_mpi
     
    178176  !      calend = 'earth_365d'
    179177
    180 #ifdef CPP_IOIPSL
    181178  if (calend == 'earth_360d') then
    182179     call ioconf_calendar('360_day')
     
    195192     call abort_gcm(modname,abort_message,1)
    196193  endif
    197 #endif
     194
    198195
    199196
     
    330327  !      endif
    331328
    332 #ifdef CPP_IOIPSL
    333329  mois = 1
    334330  heure = 0.
     
    345341  write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
    346342  write(lunout,*)jD_ref+jH_ref,anref, moisref, jourref, heureref
    347 #else
    348   ! Ehouarn: we still need to define JD_ref and JH_ref
    349   ! and since we don't know how many days there are in a year
    350   ! we set JD_ref to 0 (this should be improved ...)
    351   jD_ref=0
    352   jH_ref=0
    353 #endif
     343
    354344
    355345  if (iflag_phys.eq.1) then
     
    394384300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
    395385
    396 #ifdef CPP_IOIPSL
    397386  call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    398387  write (lunout,301)jour, mois, an
     
    401390301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    402391302 FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    403 #endif
     392
    404393
    405394  !-----------------------------------------------------------------------
     
    433422
    434423#define CPP_IOIPSL
    435 #ifdef CPP_IOIPSL
    436424  time_step = zdtvr
    437425     if (ok_dyn_ins) then
    438426        ! initialize output file for instantaneous outputs
    439427        ! t_ops = iecri * daysec ! do operations every t_ops
    440         t_ops =((1.0*iecri)/day_step) * daysec 
     428        t_ops =((1.0*iecri)/day_step) * daysec
    441429        t_wrt = daysec ! iecri * daysec ! write output every t_wrt
    442430        CALL inithist_loc(day_ref,annee_ref,time_step, &
     
    444432     endif
    445433
    446      IF (ok_dyn_ave) THEN 
     434     IF (ok_dyn_ave) THEN
    447435        ! initialize output file for averaged outputs
    448436        t_ops = iperiod * time_step ! do operations every t_ops
     
    451439     END IF
    452440  dtav = iperiod*dtvr/daysec
    453 #endif
    454 #undef CPP_IOIPSL
    455441
    456442! setting up DYN3D/XIOS inerface
     
    460446  endif
    461447
    462   ! #endif of #ifdef CPP_IOIPSL
    463448  !
    464449  !-----------------------------------------------------------------------
  • LMDZ6/trunk/libf/dyn3dmem/getparam.F90

    r2094 r5267  
    33!
    44MODULE getparam
    5 #ifdef CPP_IOIPSL
    65   USE IOIPSL
    7 #else
    8 ! if not using IOIPSL, we still need to use (a local version of) getin
    9    USE ioipsl_getincom
    10 #endif
     6
    117
    128   INTERFACE getpar
  • LMDZ6/trunk/libf/dyn3dmem/iniacademic_loc.F90

    r5214 r5267  
    1010  use exner_milieu_m, only: exner_milieu
    1111  USE parallel_lmdz, ONLY: ijb_u, ije_u, ijb_v, ije_v
    12 #ifdef CPP_IOIPSL
    1312  USE IOIPSL, ONLY: getin
    14 #else
    15   ! if not using IOIPSL, we still need to use (a local version of) getin
    16   USE ioipsl_getincom, ONLY: getin
    17 #endif
     13
    1814  USE Write_Field
    1915  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
  • LMDZ6/trunk/libf/dyn3dmem/initdynav_loc.F90

    r5246 r5267  
    44subroutine initdynav_loc(day0,anne0,tstep,t_ops,t_wrt)
    55
    6 #ifdef CPP_IOIPSL
    76  ! This routine needs IOIPSL
    87   USE IOIPSL
    9 #endif
     8
    109   USE parallel_lmdz
    1110   use Write_field
     
    5655  real :: tstep, t_ops, t_wrt
    5756
    58 #ifdef CPP_IOIPSL
    5957  ! This routine needs IOIPSL
    6058  !   Variables locales
     
    281279  call histend(histuaveid)
    282280  call histend(histvaveid)
    283 #else
    284   write(lunout,*)'initdynav_loc: Needs IOIPSL to function'
    285 #endif
    286   ! #endif of #ifdef CPP_IOIPSL
     281
    287282end subroutine initdynav_loc
  • LMDZ6/trunk/libf/dyn3dmem/initfluxsto_p.F90

    r5246 r5267  
    66        fileid,filevid,filedid)
    77
    8 #ifdef CPP_IOIPSL
    98  ! This routine needs IOIPSL
    109   USE IOIPSL
    11 #endif
     10
    1211   USE parallel_lmdz
    1312   use Write_field
     
    5857  integer :: fileid, filevid,filedid
    5958
    60 #ifdef CPP_IOIPSL
    6159  ! This routine needs IOIPSL
    6260  !   Variables locales
     
    287285  endif
    288286
    289 #else
    290   write(lunout,*)'initfluxsto_p: Needs IOIPSL to function'
    291 #endif
    292   ! #endif of #ifdef CPP_IOIPSL
     287
    293288  return
    294289end subroutine initfluxsto_p
  • LMDZ6/trunk/libf/dyn3dmem/inithist_loc.F90

    r5246 r5267  
    44subroutine inithist_loc(day0,anne0,tstep,t_ops,t_wrt)
    55
    6 #ifdef CPP_IOIPSL
    76  ! This routine needs IOIPSL
    87   USE IOIPSL
    9 #endif
     8
    109   USE parallel_lmdz
    1110   use Write_field
     
    5453  real :: tstep, t_ops, t_wrt
    5554
    56 #ifdef CPP_IOIPSL
    5755  ! This routine needs IOIPSL
    5856  !   Variables locales
     
    281279  call histend(histuid)
    282280  call histend(histvid)
    283 #else
    284   write(lunout,*)'inithist_loc: Needs IOIPSL to function'
    285 #endif
    286   ! #endif of #ifdef CPP_IOIPSL
     281
    287282end subroutine inithist_loc
  • LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.F90

    r5258 r5267  
    317317  call check_isotopes(q,ijb_u,ije_u,'leapfrog 321')
    318318
    319 #ifdef CPP_IOIPSL
    320319  if (ok_guide) then
    321320    call guide_main(itau,ucov,vcov,teta,q,masse,ps)
    322321!$OMP BARRIER
    323322  endif
    324 #endif
     323
    325324
    326325
     
    16101609!$OMP BARRIER
    16111610
    1612 #ifdef CPP_IOIPSL
    16131611         IF (ok_dynzon) THEN
    16141612
     
    16221620                   ucov,teta,pk,phi,q,masse,ps,phis)
    16231621          ENDIF
    1624 #endif
     1622
    16251623
    16261624
     
    16431641!$OMP BARRIER
    16441642
    1645 #ifdef CPP_IOIPSL
    16461643         if (ok_dyn_ins) then
    16471644             CALL writehist_loc(itau,vcov,ucov,teta,pk,phi,q, &
    16481645                   masse,ps,phis)
    16491646         endif
    1650 #endif
     1647
    16511648
    16521649          IF (ok_dyn_xios) THEN
     
    17791776           ENDIF
    17801777
    1781 #ifdef CPP_IOIPSL
    17821778          ! ! Ehouarn: re-compute geopotential for outputs
    17831779!$OMP BARRIER
     
    17961792                   ucov,teta,pk,phi,q,masse,ps,phis)
    17971793           ENDIF
    1798 #endif
     1794
    17991795
    18001796
     
    18111807
    18121808
    1813 #ifdef CPP_IOIPSL
    18141809          if (ok_dyn_ins) then
    18151810             CALL writehist_loc(itau,vcov,ucov,teta,pk,phi,q, &
    18161811                   masse,ps,phis)
    18171812          endif ! of if (ok_dyn_ins)
    1818 #endif
     1813
    18191814
    18201815          IF (ok_dyn_xios) THEN
  • LMDZ6/trunk/libf/dyn3dmem/mod_const_mpi.F90

    r4848 r5267  
    1313    USE lmdz_mpi
    1414
    15 #ifdef CPP_IOIPSL
    1615    USE IOIPSL, ONLY: getin
    17 #else
    18 ! if not using IOIPSL, we still need to use (a local version of) getin
    19     USE ioipsl_getincom, only: getin
    20 #endif
     16
    2117! Use of Oasis-MCT coupler
    2218#ifdef CPP_OMCT
  • LMDZ6/trunk/libf/dyn3dmem/parallel_lmdz.F90

    r5207 r5267  
    55  USE mod_const_mpi
    66  USE lmdz_mpi, ONLY : using_mpi
    7 #ifdef CPP_IOIPSL
    87      use IOIPSL
    9 #else
    10 ! if not using IOIPSL, we still need to use (a local version of) getin
    11       use ioipsl_getincom
    12 #endif   
     8
    139    INTEGER,PARAMETER :: halo_max=3
    1410   
  • LMDZ6/trunk/libf/dyn3dmem/writedynav_loc.F90

    r5246 r5267  
    55        masse,ps,phis)
    66
    7 #ifdef CPP_IOIPSL
    87  ! This routine needs IOIPSL
    98  USE ioipsl
    10 #endif
     9
    1110  USE parallel_lmdz
    1211  USE misc_mod
     
    6362
    6463
    65 #ifdef CPP_IOIPSL
    6664  ! This routine needs IOIPSL
    6765  !   Variables locales
     
    219217  ENDIF
    220218!$OMP END MASTER
    221 #else
    222   write(lunout,*)'writedynav_loc: Needs IOIPSL to function'
    223 #endif
    224   ! #endif of #ifdef CPP_IOIPSL
     219
    225220end subroutine writedynav_loc
  • LMDZ6/trunk/libf/dyn3dmem/writehist_loc.F90

    r5246 r5267  
    55        masse,ps,phis)
    66
    7 #ifdef CPP_IOIPSL
    87  ! This routine needs IOIPSL
    98  USE ioipsl
    10 #endif
     9
    1110  USE parallel_lmdz
    1211  USE misc_mod
     
    6362
    6463
    65 #ifdef CPP_IOIPSL
    6664  ! This routine needs IOIPSL
    6765  !   Variables locales
     
    218216  endif
    219217!$OMP END MASTER
    220 #else
    221   write(lunout,*)'writehist_loc: Needs IOIPSL to function'
    222 #endif
    223   ! #endif of #ifdef CPP_IOIPSL
     218
    224219end subroutine writehist_loc
Note: See TracChangeset for help on using the changeset viewer.