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/phylmd/etat0_netcdf.F90

    r1910 r2056  
    2929  USE netcdf, ONLY : NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR
    3030  USE indice_sol_mod
     31  use exner_hyb_m, only: exner_hyb
     32  use exner_milieu_m, only: exner_milieu
     33  use test_disvert_m, only: test_disvert
    3134#endif
    3235  IMPLICIT NONE
     
    7477  CHARACTER(LEN=80)                        :: x, fmt
    7578  INTEGER                                  :: i, j, l, ji
    76   REAL,    DIMENSION(iip1,jjp1,llm)        :: alpha, beta, pk, pls, y
     79  REAL,    DIMENSION(iip1,jjp1,llm)        :: pk, pls, y
    7780  REAL,    DIMENSION(ip1jmp1)              :: pks
    7881
     
    150153
    151154  CALL iniconst()
     155  if (pressure_exner) call test_disvert
    152156  CALL inigeom()
    153157
     
    253257  CALL pression(ip1jmp1, ap, bp, psol, p3d)
    254258  if (pressure_exner) then
    255     CALL exner_hyb(ip1jmp1, psol, p3d, alpha, beta, pks, pk, y)
     259    CALL exner_hyb(ip1jmp1, psol, p3d, pks, pk)
    256260  else
    257     CALL exner_milieu(ip1jmp1,psol,p3d,beta,pks,pk,y)
     261    CALL exner_milieu(ip1jmp1,psol,p3d, pks,pk)
    258262  endif
    259263  pls(:,:,:)=preff*(pk(:,:,:)/cpp)**(1./kappa)
Note: See TracChangeset for help on using the changeset viewer.