Changeset 5267


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

Remove CPP_IOIPSL cpp keys uses

Location:
LMDZ6/trunk/libf
Files:
3 deleted
57 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/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
    149  !! ug Pour les sorties XIOS
    1510  USE wxios
     
    3631  ENDIF
    3732
    38 #ifdef CPP_IOIPSL
    3933  call histclo
    4034  call restclo
    41 #endif
    4235  call getin_dump
    4336  ! call histclo(2)
  • LMDZ6/trunk/libf/dyn3d/bilan_dyn.F90

    r5246 r5267  
    1010  !             vQ..A=Cp T + L * ...
    1111
    12 #ifdef CPP_IOIPSL
    1312  USE IOIPSL
    14 #endif
    1513  USE comconst_mod, ONLY: pi, cpp
    1614  USE comvert_mod, ONLY: presnivs
     
    2624  !====================================================================
    2725  !
    28   !   Sous-programme consacre à des diagnostics dynamiques de base
     26  !   Sous-programme consacre des diagnostics dynamiques de base
    2927  !
    3028  !
     
    8987  real :: ww
    9088
    91   !   variables dynamiques intermédiaires
     89  !   variables dynamiques intermdiaires
    9290  REAL :: vcont(iip1,jjm,llm),ucont(iip1,jjp1,llm)
    9391  REAL :: ang(iip1,jjp1,llm),unat(iip1,jjp1,llm)
     
    9795  REAL :: bern(iip1,jjp1,llm)
    9896
    99   !   champ contenant les scalaires advectés.
     97  !   champ contenant les scalaires advects.
    10098  real :: Q(iip1,jjp1,llm,nQ)
    10199
    102   !   champs cumulés
     100  !   champs cumuls
    103101  real :: ps_cum(iip1,jjp1)
    104102  real :: masse_cum(iip1,jjp1,llm)
     
    308306  !   ----------------------------
    309307
    310   !   énergie cinétique
     308  !   �nergie cin�tique
    311309  ucont(:,:,:)=0
    312310  CALL covcont(llm,ucov,vcov,ucont,vcont)
    313311  CALL enercin(vcov,ucov,vcont,ucont,ecin)
    314312
    315   !   moment cinétique
     313  !   moment cintique
    316314  do l=1,llm
    317315     ang(:,:,l)=ucov(:,:,l)+constang(:,:)
     
    373371  enddo
    374372
    375   !    flux méridien
     373  !    flux mridien
    376374  !    -------------
    377375  do iQ=1,nQ
     
    440438
    441439  !=====================================================================
    442   !   Transport méridien
     440  !   Transport mridien
    443441  !=====================================================================
    444442
  • LMDZ6/trunk/libf/dyn3d/check_isotopes.F90

    r5214 r5267  
    44                          ntiso, iH2O, nzone, tracers, isoName,  itZonIso
    55   USE iso_params_mod,  ONLY: tnat_H216O, tnat_H217O, tnat_H218O, tnat_HDO, tnat_HTO
    6 #ifdef CPP_IOIPSL
    76   USE ioipsl,          ONLY: getin
    8 #else
    9    USE ioipsl_getincom, ONLY: getin
    10 #endif
    117   IMPLICIT NONE
    128   include "dimensions.h"
  • LMDZ6/trunk/libf/dyn3d/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
    138  USE infotrac, ONLY : type_trac
    149  use assert_m, only: assert
  • LMDZ6/trunk/libf/dyn3d/dynetat0.F90

    r5252 r5267  
    1919  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
    2020  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    21 #ifdef CPP_IOIPSL
    2221  USE IOIPSL,   ONLY: getin
    23 #else
    24   USE ioipsl_getincom, ONLY: getin
    25 #endif
    2622  USE iso_params_mod   ! tnat_* and alpha_ideal_*
    2723  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS
  • LMDZ6/trunk/libf/dyn3d/dynredem.F90

    r5084 r5267  
    44! Write the NetCDF restart file (initialization).
    55!-------------------------------------------------------------------------------
    6 #ifdef CPP_IOIPSL
    76  USE IOIPSL
    8 #endif
    97  USE strings_mod, ONLY: maxlen
    108  USE infotrac, ONLY: nqtot, tracers
     
    4644!===============================================================================
    4745  modname='dynredem0'; fil=fichnom
    48 #ifdef CPP_IOIPSL
    4946  CALL ymds2ju(annee_ref, 1, iday_end, 0.0, zjulian)
    5047  CALL ju2ymds(zjulian, yyears0, mmois0, jjour0, hours)
    51 #else
    52 ! set yyears0, mmois0, jjour0 to 0,1,1 (hours is not used)
    53   yyears0=0
    54   mmois0=1
    55   jjour0=1
    56 #endif       
     48
    5749
    5850  tab_cntrl(:)  = 0.
  • LMDZ6/trunk/libf/dyn3d/fluxstokenc.F90

    r5246 r5267  
    44SUBROUTINE fluxstokenc(pbaru,pbarv,masse,teta,phi,phis, &
    55        time_step,itau )
    6 #ifdef CPP_IOIPSL
    76  ! This routine is designed to work with ioipsl
    87
     
    162161  ENDIF ! if iadvtr.EQ.istdyn
    163162
    164 #else
    165   write(lunout,*) &
    166         'fluxstokenc: Needs IOIPSL to function'
    167 #endif
    168   ! of #ifdef CPP_IOIPSL
     163
     164
    169165  RETURN
    170166END SUBROUTINE fluxstokenc
  • LMDZ6/trunk/libf/dyn3d/friction.F90

    r5246 r5267  
    66
    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/dyn3d/gcm.F90

    r5250 r5267  
    66PROGRAM gcm
    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
    12   USE ioipsl_getincom
    13 #endif
     9
    1410
    1511
     
    173169  !      calend = 'earth_365d'
    174170
    175 #ifdef CPP_IOIPSL
    176171  if (calend == 'earth_360d') then
    177172     call ioconf_calendar('360_day')
     
    187182     call abort_gcm(modname,abort_message,1)
    188183  endif
    189 #endif
     184
    190185  !-----------------------------------------------------------------------
    191186  !
     
    325320  !      endif
    326321
    327 #ifdef CPP_IOIPSL
    328322  mois = 1
    329323  heure = 0.
     
    340334  write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
    341335  write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
    342 #else
    343   ! Ehouarn: we still need to define JD_ref and JH_ref
    344   ! and since we don't know how many days there are in a year
    345   ! we set JD_ref to 0 (this should be improved ...)
    346   jD_ref=0
    347   jH_ref=0
    348 #endif
     336
    349337
    350338
     
    391379300 FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
    392380
    393 #ifdef CPP_IOIPSL
    394381  call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    395382  write (lunout,301)jour, mois, an
     
    398385301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    399386302 FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    400 #endif
     387
    401388
    402389  !-----------------------------------------------------------------------
     
    423410  ecripar = .TRUE.
    424411
    425 #ifdef CPP_IOIPSL
    426412  time_step = zdtvr
    427413  if (ok_dyn_ins) then
    428414     ! initialize output file for instantaneous outputs
    429415     ! t_ops = iecri * daysec ! do operations every t_ops
    430      t_ops =((1.0*iecri)/day_step) * daysec 
     416     t_ops =((1.0*iecri)/day_step) * daysec
    431417     t_wrt = daysec ! iecri * daysec ! write output every t_wrt
    432418     CALL inithist(day_ref,annee_ref,time_step, &
     
    434420  endif
    435421
    436   IF (ok_dyn_ave) THEN 
     422  IF (ok_dyn_ave) THEN
    437423     ! initialize output file for averaged outputs
    438424     t_ops = iperiod * time_step ! do operations every t_ops
     
    442428  END IF
    443429  dtav = iperiod*dtvr/daysec
    444 #endif
    445   ! #endif of #ifdef CPP_IOIPSL
     430
    446431
    447432  !  Choix des frequences de stokage pour le offline
  • LMDZ6/trunk/libf/dyn3d/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/dyn3d/iniacademic.F90

    r5214 r5267  
    99  use exner_hyb_m, only: exner_hyb
    1010  use exner_milieu_m, only: exner_milieu
    11 #ifdef CPP_IOIPSL
    1211  USE IOIPSL, ONLY: getin
    13 #else
    14   ! if not using IOIPSL, we still need to use (a local version of) getin
    15   USE ioipsl_getincom, ONLY: getin
    16 #endif
     12
    1713  USE Write_Field
    1814  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
  • LMDZ6/trunk/libf/dyn3d/leapfrog.F90

    r5250 r5267  
    88
    99  !IM : pour sortir les param. du modele dans un fis. netcdf 110106
    10 #ifdef CPP_IOIPSL
    1110  use IOIPSL
    12 #endif
    1311  USE infotrac, ONLY: nqtot, isoCheck
    1412  USE guide_mod, ONLY : guide_main
     
    241239  call check_isotopes_seq(q,ip1jmp1,'leapfrog 321')
    242240
    243 #ifdef CPP_IOIPSL
    244241  if (ok_guide) then
    245242    call guide_main(itau,ucov,vcov,teta,q,masse,ps)
    246243  endif
    247 #endif
     244
    248245
    249246
     
    355352  !maf stokage du flux de masse pour traceurs OFF-LINE
    356353
    357 #ifdef CPP_IOIPSL
    358354       CALL fluxstokenc(pbaru,pbarv,masse,teta,phi,phis, &
    359355             dtvr, itau)
    360 #endif
     356
    361357
    362358
     
    451447     ENDIF ! of IF (ip_ebil_dyn.ge.1 )
    452448  !-jld
    453 #ifdef CPP_IOIPSL
     449
    454450  !IM decommenter les 6 lignes suivantes pour sortir quelques parametres dynamiques de LMDZ
    455451  !IM uncomment next 6 lines to get some parameters for LMDZ dynamics
     
    460456  !
    461457  !#include "write_paramLMDZ_dyn.h"
    462   !
    463 #endif
    464   ! #endif of #ifdef CPP_IOIPSL
     458
    465459IF (CPPKEY_PHYS) THEN
    466460     CALL calfis( lafin , jD_cur, jH_cur, &
     
    675669
    676670           IF (ok_dynzon) THEN
    677 #ifdef CPP_IOIPSL
    678671             CALL bilan_dyn(2,dtvr*iperiod,dtvr*day_step*periodav, &
    679672                   ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
    680 #endif
     673
    681674           END IF
    682675           IF (ok_dyn_ave) THEN
    683 #ifdef CPP_IOIPSL
    684676             CALL writedynav(itau,vcov, &
    685677                   ucov,teta,pk,phi,q,masse,ps,phis)
    686 #endif
     678
    687679           ENDIF
    688680
     
    704696            vnat(:,l)=vcov(:,l)/cv(:)
    705697          enddo
    706 #ifdef CPP_IOIPSL
    707698          if (ok_dyn_ins) then
    708699            ! write(lunout,*) "leapfrog: call writehist, itau=",itau
     
    714705           !  call WriteField('masse',reshape(masse,(/iip1,jmp1,llm/)))
    715706          endif ! of if (ok_dyn_ins)
    716 #endif
     707
    717708  ! For some Grads outputs of fields
    718709          if (output_grads_dyn) then
     
    812803
    813804           IF (ok_dynzon) THEN
    814 #ifdef CPP_IOIPSL
    815805             CALL bilan_dyn(2,dtvr*iperiod,dtvr*day_step*periodav, &
    816806                   ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
    817 #endif
     807
    818808           ENDIF
    819809           IF (ok_dyn_ave) THEN
    820 #ifdef CPP_IOIPSL
    821810             CALL writedynav(itau,vcov, &
    822811                   ucov,teta,pk,phi,q,masse,ps,phis)
    823 #endif
     812
    824813           ENDIF
    825814
     
    834823              vnat(:,l)=vcov(:,l)/cv(:)
    835824            enddo
    836 #ifdef CPP_IOIPSL
    837825          if (ok_dyn_ins) then
    838826             ! write(lunout,*) "leapfrog: call writehist (b)",
     
    840828            CALL writehist(itau,vcov,ucov,teta,phi,q,masse,ps,phis)
    841829          endif ! of if (ok_dyn_ins)
    842 #endif
     830
    843831  ! For some Grads outputs
    844832            if (output_grads_dyn) then
  • LMDZ6/trunk/libf/dyn3d_common/conf_planete.F90

    r4379 r5267  
    44SUBROUTINE conf_planete
    55!
    6 #ifdef CPP_IOIPSL
    76USE IOIPSL
    8 #else
    9 ! if not using IOIPSL, we still need to use (a local version of) getin
    10 USE ioipsl_getincom
    11 #endif
    127USE comconst_mod, ONLY: pi, g, molmass, kappa, cpp, omeg, rad, &
    138                        year_day, daylen, daysec, ihf
  • LMDZ6/trunk/libf/dyn3d_common/disvert.F90

    r4257 r5267  
    33SUBROUTINE disvert()
    44
    5 #ifdef CPP_IOIPSL
    65  use ioipsl, only: getin
    7 #else
    8   USE ioipsl_getincom, only: getin
    9 #endif
    106  use new_unit_m, only: new_unit
    117  use assert_m, only: assert
  • LMDZ6/trunk/libf/dyn3d_common/disvert_noterre.F90

    r5246 r5267  
    66  !    On l'utilise aussi pour Venus et Titan, legerment modifiee.
    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
    12   use ioipsl_getincom
    13 #endif
     9
    1410  USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt, &
    1511        nivsig,nivsigs,pa,preff,scaleheight
     
    2420  !
    2521  !=======================================================================
    26   !    Discretisation verticale en coordonnée hybride (ou sigma)
     22  !    Discretisation verticale en coordonne hybride (ou sigma)
    2723  !
    2824  !=======================================================================
     
    208204  ! Calcul au milieu des couches :
    209205  ! WARNING : le choix de placer le milieu des couches au niveau de
    210   ! pression intermédiaire est arbitraire et pourrait etre modifié.
     206  ! pression interm�diaire est arbitraire et pourrait etre modifi�.
    211207  ! Le calcul du niveau pour la derniere couche
    212208  ! (on met la meme distance (en log pression)  entre P(llm)
    213209  ! et P(llm -1) qu'entre P(llm-1) et P(llm-2) ) est
    214   ! Specifique.  Ce choix est spécifié ici ET dans exner_milieu.F
     210  ! Specifique.  Ce choix est sp�cifi� ici ET dans exner_milieu.F
    215211
    216212  DO l = 1, llm-1
     
    284280  ! L'objectif est de calculer newsig telle que
    285281  !   (1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig = sig
    286   ! Cela ne se résoud pas analytiquement:
    287   ! => on résoud par iterration bourrine
     282  ! Cela ne se rsoud pas analytiquement:
     283  ! => on rsoud par iterration bourrine
    288284  ! ----------------------------------------------
    289285  ! Information  : where exp(1-1./x**2) become << x
     
    320316          newsig=(X2+newsig)*0.5
    321317      end if
    322       ! Test : on arete lorsque on approxime sig à moins de 0.01 m près
     318      ! Test : on arete lorsque on approxime sig � moins de 0.01 m pr�s
    323319      ! (en pseudo altitude) :
    324320      IF(abs(10.*log(F)).LT.1.E-5) goto 999
  • LMDZ6/trunk/libf/dyn3d_common/iniconst.F90

    r2601 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 comconst_mod, ONLY: im, imp1, jm, jmp1, lllm, lllmm1, lllmp1, &
    1410                          unsim, pi, r, kappa, cpp, dtvr, dtphys
  • LMDZ6/trunk/libf/dyn3d_common/initdynav.F90

    r4046 r5267  
    33subroutine initdynav(day0,anne0,tstep,t_ops,t_wrt)
    44
    5 #ifdef CPP_IOIPSL
    65  USE IOIPSL
    7 #endif
    86  USE infotrac, ONLY : nqtot
    97  use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid, &
     
    4745  real tstep, t_ops, t_wrt
    4846
    49 #ifdef CPP_IOIPSL
    5047  ! This routine needs IOIPSL to work
    5148  !   Variables locales
     
    8279  ! Creation de 3 fichiers pour les differentes grilles horizontales
    8380  ! Restriction de IOIPSL: seulement 2 coordonnees dans le meme fichier
    84   ! Grille Scalaire       
     81  ! Grille Scalaire
    8582  call histbeg(dynhistave_file, iip1, rlong(:,1), jjp1, rlat(1,:), &
    8683       1, iip1, 1, jjp1, &
     
    185182  call histend(histuaveid)
    186183  call histend(histvaveid)
    187 #else
    188   write(lunout,*)"initdynav: Warning this routine should not be", &
    189        " used without ioipsl"
    190 #endif
    191   ! of #ifdef CPP_IOIPSL
     184
     185
    192186
    193187end subroutine initdynav
  • LMDZ6/trunk/libf/dyn3d_common/initfluxsto.F90

    r5246 r5267  
    66        fileid,filevid,filedid)
    77
    8 #ifdef CPP_IOIPSL
    98   USE IOIPSL
    10 #endif
    119  USE comconst_mod, ONLY: pi
    1210  USE comvert_mod, ONLY: nivsigs
     
    5452  integer :: fileid, filevid,filedid
    5553
    56 #ifdef CPP_IOIPSL
    5754  ! This routine needs IOIPSL to work
    5855  !   Variables locales
     
    222219  endif
    223220
    224 #else
    225   ! tell the user this routine should be run with ioipsl
    226   write(lunout,*)"initfluxsto: Warning this routine should not be", &
    227         " used without ioipsl"
    228 #endif
    229   ! of #ifdef CPP_IOIPSL
     221
     222
    230223  return
    231224end subroutine initfluxsto
  • LMDZ6/trunk/libf/dyn3d_common/inithist.F90

    r5246 r5267  
    44subroutine inithist(day0,anne0,tstep,t_ops,t_wrt)
    55
    6 #ifdef CPP_IOIPSL
    76   USE IOIPSL
    8 #endif
    97   USE infotrac, ONLY : nqtot
    108   use com_io_dyn_mod, only : histid,histvid,histuid,               &
     
    5250  real :: tstep, t_ops, t_wrt
    5351
    54 #ifdef CPP_IOIPSL
    5552  ! This routine needs IOIPSL to work
    5653  !   Variables locales
     
    186183  call histend(histuid)
    187184  call histend(histvid)
    188 #else
    189   ! tell the user this routine should be run with ioipsl
    190   write(lunout,*)"inithist: Warning this routine should not be", &
    191         " used without ioipsl"
    192 #endif
    193   ! of #ifdef CPP_IOIPSL
     185
     186
    194187  return
    195188end subroutine inithist
  • LMDZ6/trunk/libf/dyn3d_common/iso_verif_dyn.F90

    r5214 r5267  
    3333
    3434LOGICAL FUNCTION iso_verif_aberrant_nostop(x, iso, q, err_msg) RESULT(lerr)
    35 #ifdef CPP_IOIPSL
    3635   USE IOIPSL, ONLY: getin
    37 #else
    38    USE ioipsl_getincom, ONLY: getin
    39 #endif
    4036   USE iso_params_mod, ONLY: tnat_HDO
    4137   IMPLICIT NONE
  • LMDZ6/trunk/libf/dyn3d_common/writedynav.F90

    r4046 r5267  
    33subroutine writedynav(time, vcov, ucov, teta, ppk, phi, q, masse, ps, phis)
    44
    5 #ifdef CPP_IOIPSL
    65  USE ioipsl
    7 #endif
    86  USE infotrac, ONLY : nqtot
    97  use com_io_dyn_mod, only : histaveid, histvaveid, histuaveid
     
    4644  integer time
    4745
    48 #ifdef CPP_IOIPSL
    4946  ! This routine needs IOIPSL to work
    5047  !   Variables locales
     
    5350  INTEGER iq, ii, ll
    5451  real tm(ip1jmp1*llm)
    55   REAL vnat(ip1jm, llm), unat(ip1jmp1, llm) 
     52  REAL vnat(ip1jm, llm), unat(ip1jmp1, llm)
    5653  logical ok_sync
    5754  integer itau_w
     
    7572  !  Appels a histwrite pour l'ecriture des variables a sauvegarder
    7673
    77   !  Vents U 
     74  !  Vents U
    7875
    7976  call histwrite(histuaveid, 'u', itau_w, unat,  &
     
    129126  ENDIF
    130127
    131 #else
    132   write(lunout, *) "writedynav: Warning this routine should not be", &
    133        " used without ioipsl"
    134 #endif
    135   ! of #ifdef CPP_IOIPSL
     128
     129
    136130
    137131end subroutine writedynav
  • LMDZ6/trunk/libf/dyn3d_common/writehist.F90

    r5246 r5267  
    44subroutine writehist(time,vcov,ucov,teta,phi,q,masse,ps,phis)
    55
    6 #ifdef CPP_IOIPSL
    76  USE ioipsl
    8 #endif
    97  USE infotrac, ONLY : nqtot
    108  use com_io_dyn_mod, only : histid,histvid,histuid
     
    5351
    5452
    55 #ifdef CPP_IOIPSL
    5653  ! This routine needs IOIPSL to work
    5754  !   Variables locales
     
    123120    call histsync(histuid)
    124121  endif
    125 #else
    126   ! tell the user this routine should be run with ioipsl
    127   write(lunout,*)"writehist: Warning this routine should not be", &
    128         " used without ioipsl"
    129 #endif
    130   ! of #ifdef CPP_IOIPSL
     122
     123
    131124  return
    132125end subroutine writehist
  • 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
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90

    r5084 r5267  
    101101
    102102!--- Calendar choice
    103 #ifdef CPP_IOIPSL
    104103  calnd='gregorian'
    105104  SELECT CASE(calend)
     
    116115  END SELECT
    117116  WRITE(lunout,*)'CHOSEN CALENDAR: Earth '//TRIM(calnd)
    118 #endif
     117
    119118
    120119#ifdef CPP_PARA
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r5204 r5267  
    9696  USE phys_state_var_mod, ONLY: beta_aridity, delta_tsurf, awake_dens, cv_gen, &
    9797       ratqs_inter_
    98   !use ioipsl_getincom
     98  !use ioipsl
    9999  IMPLICIT NONE
    100100!-------------------------------------------------------------------------------
  • LMDZ6/trunk/libf/misc/strings_mod.F90

    r5003 r5267  
    5353!==============================================================================================================================
    5454SUBROUTINE getin_s(nam, val, def)
    55   USE ioipsl_getincom, ONLY: getin
     55  USE ioipsl, ONLY: getin
    5656  IMPLICIT NONE
    5757  CHARACTER(LEN=*), INTENT(IN)    :: nam
     
    6363!==============================================================================================================================
    6464SUBROUTINE getin_i(nam, val, def)
    65   USE ioipsl_getincom, ONLY: getin
     65  USE ioipsl, ONLY: getin
    6666  IMPLICIT NONE
    6767  CHARACTER(LEN=*), INTENT(IN)    :: nam
     
    7373!==============================================================================================================================
    7474SUBROUTINE getin_r(nam, val, def)
    75   USE ioipsl_getincom, ONLY: getin
     75  USE ioipsl, ONLY: getin
    7676  IMPLICIT NONE
    7777  CHARACTER(LEN=*), INTENT(IN)    :: nam
     
    8383!==============================================================================================================================
    8484SUBROUTINE getin_l(nam, val, def)
    85   USE ioipsl_getincom, ONLY: getin
     85  USE ioipsl, ONLY: getin
    8686  IMPLICIT NONE
    8787  CHARACTER(LEN=*), INTENT(IN)    :: nam
  • LMDZ6/trunk/libf/phy_common/abort_physic.F90

    r4600 r5267  
    22      SUBROUTINE abort_physic(modname, message, ierr)
    33     
    4 #ifdef CPP_IOIPSL
    54      USE IOIPSL
    6 #else
    7 ! if not using IOIPSL, we still need to use (a local version of) getin_dump
    8       USE ioipsl_getincom
    9 #endif
     5
    106      USE mod_phys_lmdz_para
    117      USE print_control_mod, ONLY: lunout
     
    2420
    2521      write(lunout,*) 'in abort_physic'
    26 #ifdef CPP_IOIPSL
    2722!$OMP MASTER
    2823      call histclo
     
    3227      endif
    3328!$OMP END MASTER
    34 #endif
    3529
    3630      write(lunout,*) 'Stopping in ', modname
  • LMDZ6/trunk/libf/phy_common/ioipsl_getin_p_mod.F90

    r2352 r5267  
    55! To use getin in a parallel context
    66!---------------------------------------------------------------------
    7 #ifdef CPP_IOIPSL
    87USE ioipsl, ONLY: getin
    9 #else
    10 USE ioipsl_getincom, ONLY: getin
    11 #endif
    128USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    139USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
  • LMDZ6/trunk/libf/phydev/iophy.F90

    r4729 r5267  
    3434  USE print_control_mod, ONLY: lunout, prt_level
    3535  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    36 #ifdef CPP_IOIPSL
    3736  USE ioipsl, only: flio_dom_set
    38 #endif
     37
    3938  use wxios, only: wxios_domain_param, using_xios
    4039  implicit none
  • LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r5084 r5267  
    828828       !       ENDIF
    829829
    830 #ifdef CPP_IOIPSL
    831830  IF (.NOT. using_xios) THEN
    832831    IF (.NOT.ok_all_xml) THEN
     
    836835           ll=0
    837836            DO k=1, nlevSTD
    838                bb2=clevSTD(k) 
     837               bb2=clevSTD(k)
    839838               IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
    840839                    bb2.EQ."500".OR.bb2.EQ."200".OR. &
     
    856855    ENDIF
    857856  ENDIF !.NOT.using_xios
    858 #endif
     857
    859858
    860859  IF (using_xios) THEN
     
    14701469       ENDIF
    14711470!!!!!!!!!!!! Sorties niveaux de pression NMC !!!!!!!!!!!!!!!!!!!!
    1472 #ifdef CPP_IOIPSL
    1473 
    14741471  IF (.NOT. using_xios) THEN
    1475     IF (.NOT.ok_all_xml) THEN 
     1472    IF (.NOT.ok_all_xml) THEN
    14761473         ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
    14771474         ! Champs interpolles sur des niveaux de pression
     
    15411538    ENDIF
    15421539  ENDIF
    1543 #endif
     1540
    15441541
    15451542IF (using_xios) THEN
  • LMDZ6/trunk/libf/phylmd/dyn1d/1DUTILS.h

    r5084 r5267  
    88      SUBROUTINE conf_unicol
    99!
    10 #ifdef CPP_IOIPSL
    1110      use IOIPSL
    12 #else
    13 ! if not using IOIPSL, we still need to use (a local version of) getin
    14       use ioipsl_getincom
    15 #endif
     11
    1612      USE print_control_mod, ONLY: lunout
    1713      IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/iophy.F90

    r4848 r5267  
    4343  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid_type, unstructured
    4444  USE print_control_mod, ONLY: prt_level,lunout
    45 #ifdef CPP_IOIPSL
    4645    USE ioipsl, ONLY: flio_dom_set
    47 #endif
     46
    4847  use wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init, using_xios
    4948    IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/moy_undefSTD.F90

    r5084 r5267  
    55  USE netcdf
    66  USE dimphy
    7 #ifdef CPP_IOIPSL
    87  USE phys_state_var_mod
    9 #endif
    108  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    119 
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r5252 r5267  
    14931493       !       ENDIF
    14941494
    1495 #ifdef CPP_IOIPSL
    14961495       IF (.NOT. using_xios) THEN
    14971496         IF (.NOT.ok_all_xml) THEN
     
    15011500              ll=0
    15021501              DO k=1, nlevSTD
    1503                 bb2=clevSTD(k) 
     1502                bb2=clevSTD(k)
    15041503                  IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
    15051504                       bb2.EQ."500".OR.bb2.EQ."200".OR. &
     
    15211520         ENDIF
    15221521       ENDIF
    1523 #endif
     1522
    15241523
    15251524       IF (using_xios) THEN
     
    26202619       ENDIF !ok_4xCO2atm
    26212620!!!!!!!!!!!! Sorties niveaux de pression NMC !!!!!!!!!!!!!!!!!!!!
    2622 #ifdef CPP_IOIPSL
    26232621       IF (.NOT. using_xios) THEN
    2624          IF (.NOT.ok_all_xml) THEN 
     2622         IF (.NOT.ok_all_xml) THEN
    26252623           ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
    26262624           ! Champs interpolles sur des niveaux de pression
     
    26902688         ENDIF
    26912689       ENDIF !.NOT. using_xios
    2692 #endif
     2690
    26932691
    26942692       IF (using_xios) THEN
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r5265 r5267  
    17301730          ENDIF
    17311731
    1732 #ifdef CPP_IOIPSL
    1733 
    17341732       !$OMP MASTER
    17351733       ! FH : if ok_sync=.true. , the time axis is written at each time step
     
    17621760#endif
    17631761
    1764 #endif
    17651762       ecrit_reg = ecrit_reg * un_jour
    17661763       ecrit_tra = ecrit_tra * un_jour
     
    56825679    !   Ecriture des sorties
    56835680    !=============================================================
    5684 #ifdef CPP_IOIPSL
    56855681
    56865682    ! Recupere des varibles calcule dans differents modules
     
    57425738#endif
    57435739
    5744 #endif
    57455740    ! Petit appelle de sorties pour accompagner le travail sur phyex
    57465741    if ( iflag_physiq == 1 ) then
  • LMDZ6/trunk/libf/phylmd/plevel.F90

    r5084 r5267  
    99  USE netcdf
    1010  USE dimphy
    11 #ifdef CPP_IOIPSL
    12   USE phys_state_var_mod, ONLY: missing_val_nf90
    13 #endif
     11  USE phys_state_var_mod, ONLY: missing_val_nf90
    1412  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    1513  IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/plevel_new.F90

    r5084 r5267  
    1010  USE netcdf
    1111  USE dimphy
    12 #ifdef CPP_IOIPSL
    1312  USE phys_state_var_mod, ONLY: missing_val_nf90
    14 #endif
    1513  USE wxios, ONLY: missing_val_xios=>missing_val, using_xios
    1614
  • LMDZ6/trunk/libf/phylmd/undefSTD.F90

    r5084 r5267  
    55  USE netcdf
    66  USE dimphy
    7 #ifdef CPP_IOIPSL
    87  USE phys_state_var_mod
    9 #endif
    108  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
    119
  • LMDZ6/trunk/libf/phylmdiso/isotopes_mod.F90

    r5214 r5267  
    379379
    380380SUBROUTINE getinp_s(nam, val, def, lDisp)
    381    USE ioipsl_getincom, ONLY: getin
     381   USE ioipsl, ONLY: getin
    382382   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    383383   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
     
    398398
    399399SUBROUTINE getinp_i(nam, val, def, lDisp)
    400    USE ioipsl_getincom, ONLY: getin
     400   USE ioipsl, ONLY: getin
    401401   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    402402   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
     
    417417
    418418SUBROUTINE getinp_r(nam, val, def, lDisp)
    419    USE ioipsl_getincom, ONLY: getin
     419   USE ioipsl, ONLY: getin
    420420   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    421421   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
     
    436436
    437437SUBROUTINE getinp_l(nam, val, def, lDisp)
    438    USE ioipsl_getincom, ONLY: getin
     438   USE ioipsl, ONLY: getin
    439439   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    440440   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r5265 r5267  
    19001900          ENDIF
    19011901
    1902 #ifdef CPP_IOIPSL
    1903 
    19041902       !$OMP MASTER
    19051903       ! FH : if ok_sync=.true. , the time axis is written at each time step
     
    19321930#endif
    19331931
    1934 #endif
    19351932       ecrit_reg = ecrit_reg * un_jour
    19361933       ecrit_tra = ecrit_tra * un_jour
     
    73097306    !   Ecriture des sorties
    73107307    !=============================================================
    7311 #ifdef CPP_IOIPSL
    73127308
    73137309    ! Recupere des varibles calcule dans differents modules
     
    73737369#endif
    73747370
    7375 #endif
    73767371    ! Petit appelle de sorties pour accompagner le travail sur phyex
    73777372    if ( iflag_physiq == 1 ) then
Note: See TracChangeset for help on using the changeset viewer.