Changeset 37 for trunk/libf/dyn3d


Ignore:
Timestamp:
Jan 27, 2011, 4:38:38 PM (14 years ago)
Author:
emillour
Message:

Remise en route chantier compilation -- Ehouarn

  • Modifs et corrections pour pouvoir compiler le gcm (en séentiel, avec

makelmdz_fcm pour l'instant):

  • ajout de fichiers 'arch' pour linux-64 (pour Bellonzi, avec ioipsl et en r8)
  • modification de makelmdz_fcm, ajout de la cléPP_PHYS si on compile avec une physique
  • correction de quelques typos/bugs réléàa compilation:
  • infotrac.F90 : supression des appels àlnblnk' (remplacépar len_trim)
  • bilan_dyn.F : déaration des variables znom3,znom3l,zunites3, planet_type
  • cpdet.F : "use control_mod, ONLY: planet_type" mis aux bons endroits

(idem sur cpdet.F dans dyn3dpar)

  • leapfrog.F : declaration de ztetaec(), dtec, cpdet , itau_w, duspg()
  • diagedyn.F : correction typo; attention dans diagedyn.F il y a du

include "../phylmd/YOMCST.h"
Ca va poser problè qd on change de physique....

  • Avec ces modifs, la compilation marche sans physque, avec ou sans ioipsl et avec la physique terrestre phylmd.
Location:
trunk/libf/dyn3d
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/libf/dyn3d/bilan_dyn.F

    r6 r37  
    1818      USE IOIPSL
    1919#endif
     20
     21      USE control_mod, ONLY: planet_type
    2022
    2123      IMPLICIT NONE
     
    145147      character*20,save :: znom2l(ntr,nQ)
    146148      character*10,save :: zunites2(ntr,nQ)
    147       character*10,save :: znom3(ntr,nQ)
    148       character*20,save :: znom3l(ntr,nQ)
    149       character*10,save :: zunites3(ntr,nQ)
     149      character*10,save :: znom3(nQ)
     150      character*20,save :: znom3l(nQ)
     151      character*10,save :: zunites3(nQ)
    150152
    151153      integer iave,itot,immc,itrs,istn
     
    727729            enddo
    728730         enddo
    729       enddo
     731!!      enddo
    730732
    731733c   transport vertical
     
    767769            enddo
    768770         enddo
    769       enddo
     771      enddo ! of do iQ=1,nQ
    770772
    771773c   fonction de courant pour la circulation meridienne moyenne
  • trunk/libf/dyn3d/calfis.F

    r6 r37  
    487487! ne pose pas de probleme a priori.
    488488
    489 ! #ifdef CPP_PHYS
     489#ifdef CPP_PHYS
    490490
    491491!      write(lunout,*) 'PHYSIQUE AVEC NSPLIT_PHYS=',nsplit_phys
     
    576576      zdqfi(:,:,:)=zdqfic(:,:,:)/nsplit_phys
    577577
    578 ! #endif ! CPP_PHYS
     578#endif
     579! #endif of #ifdef CPP_PHYS
    579580
    580581500   CONTINUE
  • trunk/libf/dyn3d/cpdet.F

    r5 r37  
    1414
    1515      SUBROUTINE ini_cpdet
     16     
     17      USE control_mod, ONLY: planet_type
    1618      IMPLICIT none
    1719c======================================================================
    1820c Initialisation de nu_venus et t0_venus
    1921c======================================================================
    20 
    21 ! for planet_type:
    22       USE control_mod
    2322
    2423! for cpp, nu_venus and t0_venus:
     
    4039
    4140      FUNCTION cpdet(t)
     41
     42      USE control_mod, ONLY: planet_type
    4243      IMPLICIT none
    43 
    44 ! for planet_type:
    45       USE control_mod
    4644
    4745! for cpp, nu_venus and t0_venus:
     
    6361
    6462      SUBROUTINE t2tpot(npoints, yt, yteta, ypk)
    65       IMPLICIT none
    6663c======================================================================
    6764c Arguments:
     
    7370c======================================================================
    7471
    75 ! for planet_type:
    76       USE control_mod
    77 
     72      USE control_mod, ONLY: planet_type
     73      IMPLICIT NONE
     74     
    7875! for cpp, nu_venus and t0_venus:
    7976#include "comconst.h"
     
    9794
    9895      SUBROUTINE tpot2t(npoints,yteta, yt, ypk)
    99       IMPLICIT none
    10096c======================================================================
    10197c Arguments:
     
    107103c======================================================================
    108104
    109 ! for planet_type:
    110       USE control_mod
     105      USE control_mod, ONLY: planet_type
     106      IMPLICIT NONE
    111107
    112108! for cpp, nu_venus and t0_venus:
  • trunk/libf/dyn3d/diagedyn.F

    r5 r37  
    139139     $        , h_qs_pre, qw_pre, ql_pre, qs_pre , ec_pre
    140140
     141
     142      real,external :: cpdet
    141143
    142144#ifdef CPP_EARTH
     
    209211C         Air enthalpy
    210212          zh_dair_col(i) = zh_dair_col(i)
    211 < ! ADAPTATION GCM POUR CP(T)
     213! ADAPTATION GCM POUR CP(T)
    212214     $        + cpdet(zt(i,k))*(1.-zqw(i,k)-zql(i,k)-zqs(i,k))
    213215     $                       *zairm(i,k)*zt(i,k)
  • trunk/libf/dyn3d/infotrac.F90

    r7 r37  
    316316       tname(new_iq)= tnom_0(iq)
    317317       IF (iadv(new_iq)==0) THEN
    318           ttext(new_iq)=str1(1:lnblnk(str1))
     318          ttext(new_iq)=str1(1:len_trim(str1))
    319319       ELSE
    320           ttext(new_iq)=str1(1:lnblnk(str1))//descrq(iadv(new_iq))
     320          ttext(new_iq)=str1(1:len_trim(str1))//descrq(iadv(new_iq))
    321321       END IF
    322322
  • trunk/libf/dyn3d/leapfrog.F

    r8 r37  
    116116      REAL dtetafi(ip1jmp1,llm),dqfi(ip1jmp1,llm,nqtot),dpfi(ip1jmp1)
    117117
     118      real :: duspg(ip1jmp1,llm) ! for bilan_dyn
     119
    118120c   variables pour le fichier histoire
    119121      REAL dtav      ! intervalle de temps elementaire
     
    179181c-jld
    180182
     183      integer :: itau_w ! for write_paramLMDZ_dyn.h
     184
    181185      character*80 dynhist_file, dynhistave_file
    182186      character(len=20) :: modname
     
    192196      logical , parameter :: flag_verif = .false.
    193197     
     198      ! for CP(T)
     199      real :: dtec
     200      real,external :: cpdet
     201      real :: ztetaec(ip1jmp1,llm)
    194202
    195203      itaufin   = nday*day_step
Note: See TracChangeset for help on using the changeset viewer.