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

Remove CPP_IOIPSL cpp keys uses

Location:
LMDZ6/trunk/libf/dyn3d_common
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.