Changeset 940 for LMDZ4/trunk


Ignore:
Timestamp:
Apr 7, 2008, 4:33:30 PM (17 years ago)
Author:
Laurent Fairhead
Message:

On remplace le fichier include dimphy.h par le module dimphy.F90i pour etre
coherent avec le partout
LF

Location:
LMDZ4/trunk/libf/phylmd
Files:
1 deleted
15 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/phylmd/aaam_bud.F

    r879 r940  
    1010     o                   aam, torsfc)
    1111c
     12      use dimphy
    1213      implicit none
    1314c======================================================================
     
    8889
    8990#include "dimensions.h"
    90 #include "dimphy.h"
     91ccc#include "dimphy.h"
    9192c
    9293c ARGUMENTS
  • LMDZ4/trunk/libf/phylmd/calltherm.F90

    r938 r940  
    1010     &       zmax0,f0)
    1111
     12      USE dimphy
    1213      implicit none
    1314#include "dimensions.h"
    14 #include "dimphy.h"
     15!#include "dimphy.h"
    1516#include "thermcell.h"
    1617#include "iniprint.h"
     
    4041!********************************************************
    4142!     declarations
    42       real fmc_therm(klon,klev+1),zqasc(klon,klev)
     43!      real fmc_therm(klon,klev+1),zqasc(klon,klev)
     44      real zqasc(klon,klev)
    4345      real zqla(klon,klev)
    4446      real wmax_sec(klon)
    4547      real zmax_sec(klon)
    4648      real f_sec(klon)
    47       real detrc_therm(klon,klev)
    48       save fmc_therm, detrc_therm
     49!      real detrc_therm(klon,klev)
     50!      save fmc_therm, detrc_therm
     51      REAL, SAVE, ALLOCATABLE :: fmc_therm(:,:), detrc_therm(:,:)
     52!$OMP THREADPRIVATE(fmc_therm, detrc_therm)
    4953      real clwcon0(klon,klev)
    5054      real zqsat(klon,klev)
     
    7074      REAL d_u_the(klon,klev),d_v_the(klon,klev)
    7175!
    72       real zfm_therm(klon,klev+1),zentr_therm(klon,klev),zdt
    73       save zentr_therm,zfm_therm
    74 
     76!      real zfm_therm(klon,klev+1),zentr_therm(klon,klev),zdt
     77      real zdt
     78!      save zentr_therm,zfm_therm
     79      REAL, SAVE, ALLOCATABLE :: zfm_therm(:,:),zentr_therm(:,:)
     80!$OMP THREADPRIVATE(zfm_therm, zentr_therm)
    7581      integer i,k
     82      LOGICAL, SAVE :: first=.true.
    7683!********************************************************
    7784
     
    8087!         print*,'thermiques: WARNING on passe t au lieu de t_seri'
    8188
     89         if (first) then
     90           ALLOCATE(fmc_therm(klon,klev+1))
     91           ALLOCATE(detrc_therm(klon,klev))
     92           ALLOCATE(zfm_therm(klon,klev+1))
     93           ALLOCATE(zentr_therm(klon,klev))
     94           first=.false.
     95         endif
    8296
    8397         fm_therm(:,:)=0.
  • LMDZ4/trunk/libf/phylmd/calwake.F

    r923 r940  
    2727***************************************************************
    2828*
     29      USE dimphy
    2930      IMPLICIT none
    3031c======================================================================
    3132
    3233#include "dimensions.h"
    33 #include "dimphy.h"
     34cccc#include "dimphy.h"
    3435#include "YOMCST.h"
    3536
  • LMDZ4/trunk/libf/phylmd/concvl.F

    r938 r940  
     1
    12!
    23! $Header$
     
    2324*
    2425c
    25 c      USE dimphy
     26      USE dimphy
    2627      IMPLICIT none
    2728c======================================================================
     
    6667c
    6768#include "dimensions.h"
    68 #include "dimphy.h"
     69cccccc#include "dimphy.h"
    6970c
    7071      integer NTRAC
     
    122123       INTEGER i,k,itra
    123124       REAL qs(klon,klev),qs_wake(klon,klev)
    124        REAL cbmf(klon)
    125        SAVE cbmf
    126 !       REAL cbmflast(klon)
     125cLF       REAL cbmf(klon)
     126cLF       SAVE cbmf
     127       REAL, SAVE, ALLOCATABLE :: cbmf(:)
     128c$OMP THREADPRIVATE(cbmf)!       
     129       REAL cbmflast(klon)
    127130       INTEGER ifrst
    128131       SAVE ifrst
     
    133136C     Variables supplementaires liees au bilan d'energie
    134137c      Real paire(klon)
    135       Real ql(klon,klev)
     138cLF      Real ql(klon,klev)
    136139c      Save paire
    137       Save ql
    138       Real t1(klon,klev),q1(klon,klev)
    139       Save t1,q1
     140cLF      Save ql
     141cLF      Real t1(klon,klev),q1(klon,klev)
     142cLF      Save t1,q1
    140143c      Data paire /1./
     144       REAL, SAVE, ALLOCATABLE :: ql(:,:), q1(:,:), t1(:,:)
     145c$OMP THREADPRIVATE(ql, q1, t1)
    141146c
    142147C     Variables liees au bilan d'energie et d'enthalpi
     
    162167      REAL ZRCPD
    163168c-jld ec_conser
     169cLF
     170      INTEGER nloc
     171      logical, save :: first=.true.
    164172c
    165173#include "YOMCST.h"
     
    168176#include "FCTTRE.h"
    169177c
     178      if (first) then
     179c Allocate some variables LF 04/2008
     180c
     181        allocate(cbmf(klon))
     182        allocate(ql(klon,klev))
     183        allocate(t1(klon,klev))
     184        allocate(q1(klon,klev))
     185      endif
    170186
    171187c    Copy T into Tconv
     
    189205      snow(:)=0
    190206     
    191       IF (ifrst .EQ. 0) THEN
    192          ifrst = 1
     207c      IF (ifrst .EQ. 0) THEN
     208c         ifrst = 1
     209       if (first) then
     210         first=.false.
    193211c
    194212C===========================================================================
     
    313331      else
    314332
    315       CALL cva_driver(klon,klev,klev+1,ntra,
     333cLF   necessary for gathered fields
     334      nloc=klon
     335      CALL cva_driver(klon,klev,klev+1,ntra,nloc,
    316336     $              iflag_con,iflag_mix,iflag_clos,dtime,
    317337     :              t,q,qs,t_wake,q_wake,qs_wake,u,v,tra,
  • LMDZ4/trunk/libf/phylmd/cva_driver.F

    r938 r940  
    1       SUBROUTINE cva_driver(len,nd,ndp1,ntra,iflag_con,iflag_mix,
     1      SUBROUTINE cva_driver(len,nd,ndp1,ntra,nloc,
     2     &                   iflag_con,iflag_mix,
    23     &                   iflag_clos,delt,
    34     &                   t1,q1,qs1,t1_wake,q1_wake,qs1_wake,
     
    2627***************************************************************
    2728C
     29      USE dimphy
    2830      implicit none
    2931C
     
    102104c
    103105#include "dimensions.h"
    104 #include "dimphy.h"
     106ccccc#include "dimphy.h"
    105107c
    106108c Input
     
    344346c
    345347      integer nloc
    346       parameter (nloc=klon) ! pour l'instant
     348c      parameter (nloc=klon) ! pour l'instant
    347349
    348350      integer idcum(nloc)
     
    381383      real supmax(nloc,klev)
    382384      real ale(nloc),alp(nloc),coef_clos(nloc)
    383       real mp(nloc,klev), qp(nloc,klev), up(nloc,klev), vp(nloc,klev)
    384       real wt(nloc,klev), water(nloc,klev), evap(nloc,klev)
    385       real b(nloc,klev), sigd(nloc)
    386       save mp,qp,up,vp,wt,water,evap,b
     385      real sigd(nloc)
     386!      real mp(nloc,klev), qp(nloc,klev), up(nloc,klev), vp(nloc,klev)
     387!      real wt(nloc,klev), water(nloc,klev), evap(nloc,klev)
     388!      real b(nloc,klev), sigd(nloc)
     389!      save mp,qp,up,vp,wt,water,evap,b
     390      real, save, allocatable :: mp(:,:),qp(:,:),up(:,:),vp(:,:)
     391      real, save, allocatable :: wt(:,:),water(:,:),evap(:,:), b(:,:)
     392c$OMP THREADPRIVATE(mp,qp,up,vp,wt,water,evap,b)
    387393      real  ft(nloc,klev), fq(nloc,klev)
    388394      real ftd(nloc,klev), fqd(nloc,klev)
     
    405411      real wghti(nloc,nd)
    406412      real hnk(nloc),unk(nloc),vnk(nloc)
     413      logical, save :: first=.true.
    407414
    408415c
     
    414421!-------------------------------------------------------------------
    415422
     423       if (first) then
     424         allocate(mp(nloc,klev), qp(nloc,klev), up(nloc,klev))
     425         allocate(vp(nloc,klev), wt(nloc,klev), water(nloc,klev))
     426         allocate(evap(nloc,klev), b(nloc,klev))
     427         first=.false.
     428       endif
    416429c -- set simulation flags:
    417430c   (common cvflag)
  • LMDZ4/trunk/libf/phylmd/diagphy.F

    r879 r940  
    4747C======================================================================
    4848C
     49      use dimphy
    4950      implicit none
    5051
    5152#include "dimensions.h"
    52 #include "dimphy.h"
     53ccccc#include "dimphy.h"
    5354#include "YOMCST.h"
    5455#include "YOETHF.h"
     
    209210c======================================================================
    210211 
     212      USE dimphy
    211213      IMPLICIT NONE
    212214C
    213215#include "dimensions.h"
    214 #include "dimphy.h"
     216cccccc#include "dimphy.h"
    215217#include "YOMCST.h"
    216218#include "YOETHF.h"
  • LMDZ4/trunk/libf/phylmd/ecribin.F

    r524 r940  
    33!
    44      SUBROUTINE ecribins(unit,pz)
     5      USE dimphy
    56      IMPLICIT none
    67c-----------------------------------------------------------------------
    78#include "dimensions.h"
    8 #include "dimphy.h"
     9cccc#include "dimphy.h"
    910#include "paramet.h"
    1011#include "comgeom.h"
     
    4445      END
    4546      SUBROUTINE ecribina(unit,pz)
     47      USE dimphy
    4648      IMPLICIT none
    4749c-----------------------------------------------------------------------
    4850#include "dimensions.h"
    49 #include "dimphy.h"
     51cccc#include "dimphy.h"
    5052#include "paramet.h"
    5153#include "comgeom.h"
  • LMDZ4/trunk/libf/phylmd/ecrireg.F

    r524 r940  
    33!
    44      SUBROUTINE ecriregs(unit,pz)
     5      use dimphy
    56      IMPLICIT none
    67c-----------------------------------------------------------------------
    78#include "dimensions.h"
    8 #include "dimphy.h"
     9cccc#include "dimphy.h"
    910#include "paramet.h"
    1011#include "comgeom.h"
     
    5960      END
    6061      SUBROUTINE ecrirega(unit,pz)
     62      USE dimphy
    6163      IMPLICIT none
    6264c-----------------------------------------------------------------------
    6365#include "dimensions.h"
    64 #include "dimphy.h"
     66cccc#include "dimphy.h"
    6567#include "paramet.h"
    6668#include "comgeom.h"
  • LMDZ4/trunk/libf/phylmd/read_pstoke.F

    r541 r940  
    1818C******************************************************************************
    1919
    20 
     20       USE dimphy
    2121       IMPLICIT NONE
    2222
     
    3333#include "indicesol.h"
    3434#include "control.h"
    35 #include "dimphy.h"
     35cccc#include "dimphy.h"
    3636       
    3737          integer klono,klevo,imo,jmo
  • LMDZ4/trunk/libf/phylmd/read_pstoke0.F

    r541 r940  
    1818
    1919
     20       USE dimphy
    2021       IMPLICIT NONE
    2122
     
    3233#include "indicesol.h"
    3334#include "control.h"
    34 #include "dimphy.h"
     35cccc#include "dimphy.h"
    3536         
    3637          integer kon,kev,zkon,zkev
  • LMDZ4/trunk/libf/phylmd/readsulfate.F

    r804 r940  
    537537
    538538      SUBROUTINE getso4fromfile (cyr, so4)
     539      use dimphy
    539540#include "netcdf.inc"
    540541#include "dimensions.h"     
    541 #include "dimphy.h"
     542cccc#include "dimphy.h"
    542543      CHARACTER*15 fname
    543544      CHARACTER*4 cyr
  • LMDZ4/trunk/libf/phylmd/thermcell.F

    r938 r940  
    66     s                  ,r_aspect,l_mix,w2di,tho)
    77
     8      USE dimphy
    89      IMPLICIT NONE
    910
     
    3334
    3435#include "dimensions.h"
    35 #include "dimphy.h"
     36cccc#include "dimphy.h"
    3637#include "YOMCST.h"
    3738
     
    6263      real zmix(klon), fracazmix(klon)
    6364c RC
    64       real zmax(klon),zw,zz,zw2(klon,klev+1),ztva(klon,klev),zzz
     65      real zmax(klon),zw,zw2(klon,klev+1),ztva(klon,klev)
    6566
    6667      real zlev(klon,klev+1),zlay(klon,klev)
     
    7374      real zwa(klon,klev+1)
    7475      real zld(klon,klev+1)
    75       real zwd(klon,klev+1)
     76!      real zwd(klon,klev+1)
    7677      real zsortie(klon,klev)
    7778      real zva(klon,klev)
     
    8586      real zf,zf2
    8687      real thetath2(klon,klev),wth2(klon,klev)
    87       common/comtherm/thetath2,wth2
     88!      common/comtherm/thetath2,wth2
    8889
    8990      real count_time
     91!      integer isplit,nsplit
    9092      integer isplit,nsplit,ialt
    9193      parameter (nsplit=10)
     
    128130      character*10 str10
    129131
    130       LOGICAL vtest(klon),down
     132!      LOGICAL vtest(klon),down
    131133
    132134      EXTERNAL SCOPY
    133135
    134       integer ncorrec,ll
     136      integer ncorrec
    135137      save ncorrec
    136138      data ncorrec/0/
     
    10841086     s                ,zmax,wmax)
    10851087
     1088      USE dimphy
    10861089      IMPLICIT NONE
    10871090
    10881091#include "dimensions.h"
    1089 #include "dimphy.h"
     1092cccc#include "dimphy.h"
    10901093#include "YOMCST.h"
    10911094
     
    11231126      REAL ztva(klon,klev)
    11241127      real nu(klon,klev)
    1125       real zmax0_sec(klon)
    1126       save zmax0_sec
     1128!      real zmax0_sec(klon)
     1129!      save zmax0_sec
     1130       REAL, SAVE, ALLOCATABLE :: zmax0_sec(:)
     1131c$OMP THREADPRIVATE(zmax0_sec)
     1132      logical, save :: first = .true.
     1133
     1134      if (first) then
     1135        allocate(zmax0_sec(klon))
     1136        first=.false.
     1137      endif
    11271138
    11281139      do l=1,nlay
  • LMDZ4/trunk/libf/phylmd/thermcell_main.F90

    r938 r940  
    1212     &                  ,zmax0, f0)
    1313
     14      use dimphy
    1415      IMPLICIT NONE
    1516
     
    4041
    4142#include "dimensions.h"
    42 #include "dimphy.h"
     43!#include "dimphy.h"
    4344#include "YOMCST.h"
    4445#include "YOETHF.h"
     
    9697      real thetath2(klon,klev),wth2(klon,klev),wth3(klon,klev)
    9798      real q2(klon,klev)
    98       common/comtherm/thetath2,wth2
     99!      common/comtherm/thetath2,wth2
    99100   
    100101      real ratqscth(klon,klev)
  • LMDZ4/trunk/libf/phylmd/thermcell_old.F

    r878 r940  
    77     s                  ,r_aspect,l_mix,w2di,tho)
    88
     9      USE dimphy
    910      IMPLICIT NONE
    1011
     
    3435
    3536#include "dimensions.h"
    36 #include "dimphy.h"
     37cccc#include "dimphy.h"
    3738#include "YOMCST.h"
    3839
     
    8081      real zf,zf2
    8182      real thetath2(klon,klev),wth2(klon,klev)
    82       common/comtherm/thetath2,wth2
     83!      common/comtherm/thetath2,wth2
    8384
    8485      real count_time
     
    106107      real fmc(klon,klev+1)
    107108
    108       character*2 str2
    109       character*10 str10
     109      character (len=2) :: str2
     110      character (len=10) :: str10
    110111
    111112      LOGICAL vtest(klon),down
     
    803804     s                  ,r_aspect,l_mix,w2di,tho)
    804805
     806      USE dimphy
    805807      IMPLICIT NONE
    806808
     
    830832
    831833#include "dimensions.h"
    832 #include "dimphy.h"
     834cccc#include "dimphy.h"
    833835#include "YOMCST.h"
    834836#include "YOETHF.h"
     
    871873      real w_est(klon,klev+1)
    872874con garde le zmax du pas de temps precedent
    873       real zmax0(klon)
    874       save zmax0
    875       real zmix0(klon)
    876       save zmix0
     875c      real zmax0(klon)
     876c      save zmax0
     877c      real zmix0(klon)
     878c      save zmix0
     879      REAL, SAVE, ALLOCATABLE :: zmax0(:), zmix0(:)
     880c$OMP THREADPRIVATE(zmax0, zmix0)
    877881
    878882      real zlev(klon,klev+1),zlay(klon,klev)
     
    903907      real q2(klon,klev)
    904908      real dtheta(klon,klev)
    905       common/comtherm/thetath2,wth2
     909!      common/comtherm/thetath2,wth2
    906910   
    907911      real ratqscth(klon,klev)
     
    964968      real nu_max
    965969      real nu_r
    966       real f(klon), f0(klon)
    967       save f0
     970      real f(klon)
     971c      real f(klon), f0(klon)
     972c     save f0
     973      REAL,SAVE, ALLOCATABLE :: f0(:)
     974c$OMP THREADPRIVATE(f0)
     975
    968976      real f_old
    969977      real zlevinter(klon)
    970       logical first
     978      logical, save :: first = .true.
    971979c      data first /.false./
    972980c      save first
     
    9981006c   ---------------
    9991007c
     1008      if (first) then
     1009        allocate(zmix0(klon))
     1010        allocate(zmax0(klon))
     1011        allocate(f0(klon))
     1012        first=.false.
     1013      endif
     1014
    10001015       sorties=.false.
    10011016c     print*,'NOUVEAU DETR PLUIE '
     
    25852600     s                  ,r_aspect,l_mix,w2di,tho)
    25862601
     2602      USE dimphy
    25872603      IMPLICIT NONE
    25882604
     
    26122628
    26132629#include "dimensions.h"
    2614 #include "dimphy.h"
     2630cccc#include "dimphy.h"
    26152631#include "YOMCST.h"
    26162632#include "YOETHF.h"
     
    26692685      real zf,zf2
    26702686      real thetath2(klon,klev),wth2(klon,klev)
    2671       common/comtherm/thetath2,wth2
     2687!      common/comtherm/thetath2,wth2
    26722688
    26732689      real count_time
     
    36933709     s                  ,r_aspect,l_mix,w2di,tho)
    36943710
     3711      USE dimphy
    36953712      IMPLICIT NONE
    36963713
     
    37203737
    37213738#include "dimensions.h"
    3722 #include "dimphy.h"
     3739cccc#include "dimphy.h"
    37233740#include "YOMCST.h"
    37243741
     
    37723789      real zf,zf2
    37733790      real thetath2(klon,klev),wth2(klon,klev)
    3774       common/comtherm/thetath2,wth2
     3791!      common/comtherm/thetath2,wth2
    37753792
    37763793      real count_time
     
    46654682      subroutine dqthermcell(ngrid,nlay,ptimestep,fm,entr,
    46664683     .           masse,q,dq,qa)
     4684      USE dimphy
    46674685      implicit none
    46684686
     
    46764694
    46774695#include "dimensions.h"
    4678 #include "dimphy.h"
     4696cccc#include "dimphy.h"
    46794697
    46804698      integer ngrid,nlay
     
    47644782     .    ,fraca,larga
    47654783     .    ,u,v,du,dv,ua,va)
     4784      USE dimphy
    47664785      implicit none
    47674786
     
    47754794
    47764795#include "dimensions.h"
    4777 #include "dimphy.h"
     4796cccc#include "dimphy.h"
    47784797
    47794798      integer ngrid,nlay
     
    48774896      subroutine dqthermcell2(ngrid,nlay,ptimestep,fm,entr,masse,frac
    48784897     .    ,q,dq,qa)
     4898      USE dimphy
    48794899      implicit none
    48804900
     
    48884908
    48894909#include "dimensions.h"
    4890 #include "dimphy.h"
     4910cccc#include "dimphy.h"
    48914911
    48924912      integer ngrid,nlay
     
    49574977     .    ,fraca,larga
    49584978     .    ,u,v,du,dv,ua,va)
     4979      use dimphy
    49594980      implicit none
    49604981
     
    49684989
    49694990#include "dimensions.h"
    4970 #include "dimphy.h"
     4991cccc#include "dimphy.h"
    49714992
    49724993      integer ngrid,nlay
     
    50935114     s                  ,r_aspect,l_mix,w2di,tho)
    50945115
     5116      use dimphy
    50955117      IMPLICIT NONE
    50965118
     
    51205142
    51215143#include "dimensions.h"
    5122 #include "dimphy.h"
     5144cccc#include "dimphy.h"
    51235145#include "YOMCST.h"
    51245146
     
    51725194      real zf,zf2
    51735195      real thetath2(klon,klev),wth2(klon,klev)
    5174       common/comtherm/thetath2,wth2
     5196!      common/comtherm/thetath2,wth2
    51755197
    51765198      real count_time
  • LMDZ4/trunk/libf/phylmd/wake.F

    r879 r940  
    2222***************************************************************
    2323c
     24      USE dimphy
    2425      IMPLICIT none
    2526c============================================================================
     
    112113
    113114#include "dimensions.h"
    114 #include "dimphy.h"
     115cccc#include "dimphy.h"
    115116#include "YOMCST.h"
    116117#include "cvthermo.h"
Note: See TracChangeset for help on using the changeset viewer.