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

Remove CPP_IOIPSL cpp keys uses

Location:
LMDZ6/trunk/libf/dyn3d
Files:
12 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
Note: See TracChangeset for help on using the changeset viewer.