Ignore:
Timestamp:
Jun 11, 2014, 3:46:46 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r1997:2055 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dmem/iniacademic_loc.F90

    r1910 r2056  
    44SUBROUTINE iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
    55
     6  use exner_hyb_m, only: exner_hyb
     7  use exner_milieu_m, only: exner_milieu
    68  USE filtreg_mod
    79  USE infotrac, ONLY : nqtot
     
    5860  REAL pks(ip1jmp1)                      ! exner au  sol
    5961  REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
    60   REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
    6162  REAL phi(ip1jmp1,llm)                  ! geopotentiel
    6263  REAL ddsin,zsig,tetapv,w_pv  ! variables auxiliaires
     
    7576
    7677  REAL zdtvr
    77   real,allocatable :: alpha(:,:),beta(:,:)
    7878 
    7979  character(len=*),parameter :: modname="iniacademic"
     
    219219       allocate(masse_glo(ip1jmp1,llm))
    220220       allocate(phis_glo(ip1jmp1))
    221        allocate(alpha(ip1jmp1,llm))
    222        allocate(beta(ip1jmp1,llm))
    223221
    224222        ! surface pressure
     
    238236        CALL pression ( ip1jmp1, ap, bp, ps_glo, p       )
    239237        if (pressure_exner) then
    240           CALL exner_hyb( ip1jmp1, ps_glo, p,alpha,beta, pks, pk, pkf )
     238          CALL exner_hyb( ip1jmp1, ps_glo, p, pks, pk )
    241239        else
    242           call exner_milieu(ip1jmp1,ps_glo,p,beta,pks,pk,pkf)
     240          call exner_milieu(ip1jmp1,ps_glo,p,pks,pk)
    243241        endif
    244242        CALL massdair(p,masse_glo)
     
    301299        deallocate(ps_glo)
    302300        deallocate(phis_glo)
    303         deallocate(alpha)
    304         deallocate(beta)
    305301     ENDIF ! of IF (.NOT. read_start)
    306302  endif academic_case
Note: See TracChangeset for help on using the changeset viewer.