Changeset 1616 for LMDZ5/trunk/libf/dyn3d/integrd.F
- Timestamp:
- Feb 17, 2012, 12:59:00 PM (13 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/dyn3d/integrd.F
r1550 r1616 4 4 SUBROUTINE integrd 5 5 $ ( nq,vcovm1,ucovm1,tetam1,psm1,massem1, 6 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis,finvmaold ) 6 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis !,finvmaold 7 & ) 7 8 8 9 use control_mod, only : planet_type … … 34 35 #include "temps.h" 35 36 #include "serre.h" 37 #include "iniprint.h" 36 38 37 39 c Arguments: 38 40 c ---------- 39 41 40 INTEGER nq 41 42 REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm) 43 REAL q(ip1jmp1,llm,nq) 44 REAL ps(ip1jmp1),masse(ip1jmp1,llm),phis(ip1jmp1) 45 46 REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm) 47 REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1),massem1(ip1jmp1,llm) 48 49 REAL dv(ip1jm,llm),du(ip1jmp1,llm) 50 REAL dteta(ip1jmp1,llm),dp(ip1jmp1) 51 REAL dq(ip1jmp1,llm,nq), finvmaold(ip1jmp1,llm) 42 integer,intent(in) :: nq ! number of tracers to handle in this routine 43 real,intent(inout) :: vcov(ip1jm,llm) ! covariant meridional wind 44 real,intent(inout) :: ucov(ip1jmp1,llm) ! covariant zonal wind 45 real,intent(inout) :: teta(ip1jmp1,llm) ! potential temperature 46 real,intent(inout) :: q(ip1jmp1,llm,nq) ! advected tracers 47 real,intent(inout) :: ps(ip1jmp1) ! surface pressure 48 real,intent(inout) :: masse(ip1jmp1,llm) ! atmospheric mass 49 real,intent(in) :: phis(ip1jmp1) ! ground geopotential !!! unused 50 ! values at previous time step 51 real,intent(inout) :: vcovm1(ip1jm,llm) 52 real,intent(inout) :: ucovm1(ip1jmp1,llm) 53 real,intent(inout) :: tetam1(ip1jmp1,llm) 54 real,intent(inout) :: psm1(ip1jmp1) 55 real,intent(inout) :: massem1(ip1jmp1,llm) 56 ! the tendencies to add 57 real,intent(in) :: dv(ip1jm,llm) 58 real,intent(in) :: du(ip1jmp1,llm) 59 real,intent(in) :: dteta(ip1jmp1,llm) 60 real,intent(in) :: dp(ip1jmp1) 61 real,intent(in) :: dq(ip1jmp1,llm,nq) !!! unused 62 ! real,intent(out) :: finvmaold(ip1jmp1,llm) !!! unused 52 63 53 64 c Local: … … 55 66 56 67 REAL vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1) 57 REAL massescr( ip1jmp1,llm ), finvmasse(ip1jmp1,llm) 68 REAL massescr( ip1jmp1,llm ) 69 ! REAL finvmasse(ip1jmp1,llm) 58 70 REAL p(ip1jmp1,llmp1) 59 71 REAL tpn,tps,tppn(iim),tpps(iim) … … 61 73 REAL deltap( ip1jmp1,llm ) 62 74 63 INTEGER l,ij,iq 75 INTEGER l,ij,iq,i,j 64 76 65 77 REAL SSUM … … 88 100 DO ij = 1,ip1jmp1 89 101 IF( ps(ij).LT.0. ) THEN 90 PRINT*,' Au point ij = ',ij, ' , pression sol neg. ', ps(ij) 91 print *, ' dans integrd' 92 stop 1 102 write(lunout,*) "integrd: negative surface pressure ",ps(ij) 103 write(lunout,*) " at node ij =", ij 104 ! since ij=j+(i-1)*jjp1 , we have 105 j=modulo(ij,jjp1) 106 i=1+(ij-j)/jjp1 107 write(lunout,*) " lon = ",rlonv(i)*180./pi, " deg", 108 & " lat = ",rlatu(j)*180./pi, " deg" 109 stop 93 110 ENDIF 94 111 ENDDO … … 110 127 CALL massdair ( p , masse ) 111 128 112 CALL SCOPY( ijp1llm , masse, 1, finvmasse, 1 ) 113 CALL filtreg( finvmasse, jjp1, llm, -2, 2, .TRUE., 1 ) 129 ! Ehouarn : we don't use/need finvmaold and finvmasse, 130 ! so might as well not compute them 131 ! CALL SCOPY( ijp1llm , masse, 1, finvmasse, 1 ) 132 ! CALL filtreg( finvmasse, jjp1, llm, -2, 2, .TRUE., 1 ) 114 133 c 115 134 … … 218 237 ENDDO 219 238 220 221 CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 )239 ! Ehouarn: forget about finvmaold 240 ! CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 ) 222 241 223 242 endif ! of if (planet_type.eq."earth")
Note: See TracChangeset
for help on using the changeset viewer.