Ignore:
Timestamp:
Nov 6, 2006, 4:51:16 PM (18 years ago)
Author:
Laurent Fairhead
Message:

Modifications pour rendre INCA plus independant de LMDZ ACo
LF

Location:
LMDZ4/branches/V3_test/libf/dyn3d
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/V3_test/libf/dyn3d/advtrac.F

    r703 r726  
    88     *                   p,  masse,q,iapptrac,teta,
    99     *                  flxw,
    10      *                  pk,
    11      *                  mmt_adj,
    12      *                  hadv_flg)
     10     *                  pk)
    1311#else
    1412      SUBROUTINE advtrac(pbaru,pbarv ,
     
    5149      REAL pk(ip1jmp1,llm)
    5250#ifdef INCA
    53       INTEGER            :: hadv_flg(nqmx)
    54       REAL               :: mmt_adj(ip1jmp1,llm,1)
    5551      REAL               :: flxw(ip1jmp1,llm)
    5652#endif
     
    215211#ifdef INCA
    216212       do iiq = iq+1, iq+3
    217          q(:,:,iiq)=q(:,:,iiq)*mmt_adj(:,:,1)
     213c         q(:,:,iiq)=q(:,:,iiq)*mmt_adj(:,:,1)
     214          q(:,:,iiq)=q(:,:,iiq)*1
    218215       enddo
    219216#endif
     
    233230#ifdef INCA
    234231       do iiq = iq+1, iq+9
    235          q(:,:,iiq)=q(:,:,iiq)*mmt_adj(:,:,1)
     232c         q(:,:,iiq)=q(:,:,iiq)*mmt_adj(:,:,1)
     233         q(:,:,iiq)=q(:,:,iiq)*1
    236234       enddo
    237235#endif
  • LMDZ4/branches/V3_test/libf/dyn3d/advtrac.h

    r524 r726  
    55c INCLUDE 'advtrac.h'
    66
    7       COMMON/advtr/iadv,hadv,vadv,tnom,tname,ttext,niadv
     7      COMMON/advtr/iadv,hadv,vadv,tnom,tname,ttext,niadv,
     8     &     nbtrac, nprath, mmt_adj, hadv_flg, vadv_flg, conv_flg,
     9     &     pbl_flg, tracnam
    810      INTEGER iadv(nqmx) ! indice schema de transport
    911      INTEGER hadv(nqmx) ! indice schema transport horizontal
     
    1315      character*10 tname(nqmx) ! nom du traceur pour restart
    1416      character*13 ttext(nqmx) ! nom long du traceur pour sorties
     17
     18
     19      integer nbtrac
     20      integer nprath
     21      real    mmt_adj(iim+1,jjm+1,llm, 1)
     22      integer hadv_flg(nqmx)
     23      integer vadv_flg(nqmx)
     24      integer conv_flg(nqmx-2)
     25      integer pbl_flg(nqmx-2)
     26      character*8 tracnam(nqmx-2)
    1527c-----------------------------------------------------------------------
  • LMDZ4/branches/V3_test/libf/dyn3d/caladvtrac.F

    r703 r726  
    88     *                   p ,masse, dq ,  teta,
    99     *                   flxw,
    10      *                   pk,
    11      *                   mmt_adj,
    12      *                   hadv_flg)
     10     *                   pk)
    1311#else
    1412            SUBROUTINE caladvtrac(q,pbaru,pbarv ,
     
    4240      REAL teta( ip1jmp1,llm),pk( ip1jmp1,llm)
    4341#ifdef INCA
    44       INTEGER            :: hadv_flg(nqmx)
    45       REAL               :: mmt_adj(iip1,jjp1,llm,1)
    4642      REAL               :: flxw(ip1jmp1,llm)
    4743#endif
     
    7773     *             p,  masse,q,iapptrac, teta,
    7874     .             flxw,
    79      .             pk,
    80      .             mmt_adj,
    81      .             hadv_flg)
     75     .             pk)
    8276#else
    8377      CALL advtrac( pbaru,pbarv,
  • LMDZ4/branches/V3_test/libf/dyn3d/gcm.F

    r704 r726  
    5858#include "iniprint.h"
    5959#include "tracstoke.h"
    60 
     60#include "advtrac.h"
    6161
    6262      INTEGER         longcles
     
    145145      dynhistave_file = 'dyn_hist_ave.nc'
    146146
     147c initialisation Anne
     148      hadv_flg(:) = 0.
     149      vadv_flg(:) = 0.
     150      conv_flg(:) = 0.
     151      pbl_flg(:)  = 0.
     152      tracnam(:)  = '        '
     153      nprath = 1
     154      nbtrac = 0
     155      mmt_adj(:,:,:,:) = 1
     156
     157
    147158c--------------------------------------------------------------------------
    148159c   Iflag_phys controle l'appel a la physique :
     
    188199      call init_phys_openmp
    189200      call InitComgeomphy
     201
     202#ifdef INCA
     203      call init_const_lmdz(nbtrac,anneeref,dayref,iphysiq,day_step,nday)
     204      call init_inca_para(iim,jjm+1,klon2,phy_size,klon_para_nb)
     205#endif
     206
    190207c
    191208c
     
    222239      endif
    223240
     241#ifdef INCA
     242      call init_inca_dim(klon,llm,iim,jjm,
     243     $     rlonu,rlatu,rlonv,rlatv)
     244#endif
    224245
    225246
  • LMDZ4/branches/V3_test/libf/dyn3d/guide.F

    r703 r726  
    367367                if (first.and.ini_anal) vcov(ij,l)=a
    368368            enddo
    369             if (first.and.ini_anal) vcov(ij,l)=a
    370369         enddo
    371370      endif
  • LMDZ4/branches/V3_test/libf/dyn3d/iniadvtrac.F

    r703 r726  
    66      subroutine iniadvtrac(nq)
    77      USE ioipsl
    8 #ifdef INCA
    9       USE transport_controls, only : hadv_flg, vadv_flg
    10       USE species_names
    11       USE chemshut
    12 #endif
    138      IMPLICIT NONE
    149c=======================================================================
     
    5954      descrq(20)='SLP'
    6055      descrq(30)='PRA'
     56
     57#ifdef INCA
     58
     59      CALL init_transport(
     60     $     hadv_flg,
     61     $     vadv_flg,
     62     $     conv_flg,
     63     $     pbl_flg,
     64     $     tracnam)
     65#endif
    6166
    6267c-----------------------------------------------------------------------
  • LMDZ4/branches/V3_test/libf/dyn3d/leapfrog.F

    r703 r726  
    77     &                    time_0)
    88
    9 #ifdef INCA
    10       USE transport_controls, ONLY : hadv_flg, mmt_adj
    11 #endif
    129
    1310cIM : pour sortir les param. du modele dans un fis. netcdf 110106
     
    6158#include "com_io_dyn.h"
    6259#include "iniprint.h"
    63 
     60#include "advtrac.h"
    6461c#include "tracstoke.h"
    6562
     
    297294     *                      p, masse, dq,  teta,
    298295     .             flxw,
    299      .             pk,
    300      .             mmt_adj,
    301      .             hadv_flg)
     296     .             pk)
    302297#else
    303298             CALL caladvtrac(q,pbaru,pbarv,
Note: See TracChangeset for help on using the changeset viewer.