Changeset 7 for trunk/libf/dyn3d
- Timestamp:
- Oct 28, 2010, 9:30:04 AM (14 years ago)
- Location:
- trunk/libf/dyn3d
- Files:
-
- 11 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/libf/dyn3d/addfi.F
r6 r7 1 1 ! 2 ! $ Header$2 ! $Id: addfi.F 1446 2010-10-22 09:27:25Z emillour $ 3 3 ! 4 4 SUBROUTINE addfi(pdt, leapf, forward, … … 7 7 8 8 USE infotrac, ONLY : nqtot 9 USE control_mod, ONLY : planet_type 9 10 IMPLICIT NONE 10 11 c … … 116 117 ENDDO 117 118 118 DO iq = 1, nqtot 119 IF ((planet_type.eq.'earth').and.(iq.le.2)) THEN 119 if (planet_type=="earth") then 120 ! earth case, special treatment for first 2 tracers (water) 121 DO iq = 1, 2 120 122 DO k = 1,llm 121 123 DO j = 1,ip1jmp1 … … 124 126 ENDDO 125 127 ENDDO 126 ELSE 128 ENDDO 129 130 DO iq = 3, nqtot 127 131 DO k = 1,llm 128 132 DO j = 1,ip1jmp1 … … 131 135 ENDDO 132 136 ENDDO 133 ENDDO 137 ENDDO 138 else 139 ! general case, treat all tracers equally) 140 DO iq = 1, nqtot 141 DO k = 1,llm 142 DO j = 1,ip1jmp1 143 pq(j,k,iq)= pq(j,k,iq) + pdqfi(j,k,iq) * pdt 144 pq(j,k,iq)= AMAX1( pq(j,k,iq), qtestt ) 145 ENDDO 146 ENDDO 147 ENDDO 148 endif ! of if (planet_type=="earth") 134 149 135 150 DO ij = 1, iim -
trunk/libf/dyn3d/advtrac.F
r1 r7 1 1 ! 2 ! $Id: advtrac.F 14 03 2010-07-01 09:02:53Z fairhead$2 ! $Id: advtrac.F 1446 2010-10-22 09:27:25Z emillour $ 3 3 ! 4 4 c … … 236 236 call vlsplt(q(1,1,iq),2.,massem,wg,pbarug,pbarvg,dtvr) 237 237 238 239 238 c ---------------------------------------------------------------- 240 239 c Schema "pseudo amont" + test sur humidite specifique -
trunk/libf/dyn3d/caladvtrac.F
r6 r7 1 1 ! 2 ! $Id: caladvtrac.F 14 03 2010-07-01 09:02:53Z fairhead$2 ! $Id: caladvtrac.F 1446 2010-10-22 09:27:25Z emillour $ 3 3 ! 4 4 c … … 9 9 c 10 10 USE infotrac 11 USE control_mod 11 USE control_mod, ONLY : iapp_tracvl,planet_type 12 12 13 13 IMPLICIT NONE … … 30 30 c ---------- 31 31 REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm),masse(ip1jmp1,llm) 32 REAL p( ip1jmp1,llmp1),q( ip1jmp1,llm,nqtot),dq( ip1jmp1,llm,2 ) 32 REAL p( ip1jmp1,llmp1),q( ip1jmp1,llm,nqtot) 33 real :: dq(ip1jmp1,llm,nqtot) 33 34 REAL teta( ip1jmp1,llm),pk( ip1jmp1,llm) 34 35 REAL :: flxw(ip1jmp1,llm) … … 49 50 cc 50 51 c 52 ! Earth-specific stuff for the first 2 tracers (water) 53 if (planet_type.eq."earth") then 51 54 C initialisation 52 dq = 0. 53 54 IF (planet_type.eq."earth") THEN 55 ! Earth-specific treatment of first 2 tracers (water) 56 57 CALL SCOPY( 2 * ijp1llm, q, 1, dq, 1 ) 58 55 dq(:,:,1:2)=q(:,:,1:2) 56 59 57 c test des valeurs minmax 60 58 cc CALL minmaxq(q(1,1,1),1.e33,-1.e33,'Eau vapeur (a) ') 61 59 cc CALL minmaxq(q(1,1,2),1.e33,-1.e33,'Eau liquide(a) ') 62 60 endif ! of if (planet_type.eq."earth") 63 61 c advection 64 62 … … 66 64 * p, masse,q,iapptrac, teta, 67 65 . flxw, pk) 66 68 67 c 69 68 70 IF( iapptrac.EQ.iapp_tracvl ) THEN 69 IF( iapptrac.EQ.iapp_tracvl ) THEN 70 if (planet_type.eq."earth") then 71 ! Earth-specific treatment for the first 2 tracers (water) 71 72 c 72 73 cc CALL minmaxq(q(1,1,1),1.e33,-1.e33,'Eau vapeur ') … … 100 101 ENDDO 101 102 c 102 ELSE 103 DO iq = 1 , 2 104 DO l = 1, llm 105 DO ij = 1,ip1jmp1 106 dq(ij,l,iq) = 0. 107 ENDDO 108 ENDDO 109 ENDDO 103 endif ! of if (planet_type.eq."earth") 104 ELSE 105 if (planet_type.eq."earth") then 106 ! Earth-specific treatment for the first 2 tracers (water) 107 dq(:,:,1:2)=0. 108 endif ! of if (planet_type.eq."earth") 109 ENDIF ! of IF( iapptrac.EQ.iapp_tracvl ) 110 110 111 112 ENDIF ! iapptrac VS iapp_tracvl113 114 ELSE ! not Earth115 116 c advection117 118 CALL advtrac( pbaru,pbarv,119 * p, masse,q,iapptrac, teta,120 . flxw, pk)121 c122 123 ENDIF ! planet_type124 125 c126 127 c ... On appelle qminimum uniquement pour l'eau vapeur et liquide ..128 129 130 RETURN131 111 END 132 112 -
trunk/libf/dyn3d/ener.h
r1 r7 1 1 ! 2 ! $ Header$2 ! $Id: ener.h 1447 2010-10-22 16:18:27Z jghattas $ 3 3 ! 4 c----------------------------------------------------------------------- 5 c INCLUDE 'ener.h' 4 ! ATTENTION!!!!: ce fichier include est compatible format fixe/format libre 5 ! veillez à n'utiliser que des ! pour les commentaires 6 ! et à bien positionner les & des lignes de continuation 7 ! (les placer en colonne 6 et en colonne 73) 8 ! 9 ! INCLUDE 'ener.h' 6 10 7 COMMON/ener/ang0,etot0,ptot0,ztot0,stot0, 8 * ang,etot,ptot,ztot,stot,rmsdpdt ,9 *rmsv,gtot(llmm1)11 COMMON/ener/ang0,etot0,ptot0,ztot0,stot0, & 12 & ang,etot,ptot,ztot,stot,rmsdpdt , & 13 & rmsv,gtot(llmm1) 10 14 11 REAL ang0,etot0,ptot0,ztot0,stot0, 12 sang,etot,ptot,ztot,stot,rmsdpdt,rmsv,gtot15 REAL ang0,etot0,ptot0,ztot0,stot0, & 16 & ang,etot,ptot,ztot,stot,rmsdpdt,rmsv,gtot 13 17 14 c-----------------------------------------------------------------------18 !----------------------------------------------------------------------- -
trunk/libf/dyn3d/gcm.F
r6 r7 1 1 ! 2 ! $Id: gcm.F 14 03 2010-07-01 09:02:53Z fairhead$2 ! $Id: gcm.F 1446 2010-10-22 09:27:25Z emillour $ 3 3 ! 4 4 c … … 182 182 ! dynamique -> physique pour l'initialisation 183 183 ! Ehouarn : temporarily (?) keep this only for Earth 184 if (planet_type.eq."earth") then 185 #ifdef CPP_EARTH 184 ! if (planet_type.eq."earth") then 185 !#ifdef CPP_EARTH 186 #ifdef CPP_PHYS 186 187 CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/)) 187 188 call InitComgeomphy 188 189 #endif 189 endif190 ! endif 190 191 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 191 192 c … … 439 440 ! SANS physique, car iniphysiq.F est dans le repertoire phy[]... 440 441 ! Il faut une cle CPP_PHYS 441 !#ifdef CPP_PHYS442 #ifdef CPP_PHYS 442 443 CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys , 443 444 , latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp ) 444 !#endif ! CPP_PHYS445 #endif ! CPP_PHYS 445 446 call_iniphys=.false. 446 447 ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1)) -
trunk/libf/dyn3d/grid_noro.F
r1 r7 1 1 ! 2 ! $Id: grid_noro.F 14 03 2010-07-01 09:02:53Z fairhead$2 ! $Id: grid_noro.F 1442 2010-10-18 08:31:31Z jghattas $ 3 3 ! 4 4 c … … 458 458 C MAKE A MOVING AVERAGE OVER 9 GRIDPOINTS OF THE X FIELDS 459 459 460 PARAMETER (ISMo=400,JSMo=200) 461 REAL X(IMAR,JMAR),XF(ISMo,JSMo) 460 REAL X(IMAR,JMAR),XF(IMAR,JMAR) 462 461 real WEIGHTpb(-1:1,-1:1) 463 462 464 if(imar.gt.ismo) stop'surdimensionner ismo dans mva9 (grid_noro)' 465 if(jmar.gt.jsmo) stop'surdimensionner jsmo dans mva9 (grid_noro)' 466 463 467 464 SUM=0. 468 465 DO IS=-1,1 -
trunk/libf/dyn3d/infotrac.F90
r6 r7 31 31 32 32 SUBROUTINE infotrac_init 33 34 33 USE control_mod 35 36 34 IMPLICIT NONE 37 35 !======================================================================= … … 63 61 CHARACTER(len=1), DIMENSION(3) :: txts 64 62 CHARACTER(len=2), DIMENSION(9) :: txtp 65 CHARACTER(len= 13) :: str1,str263 CHARACTER(len=23) :: str1,str2 66 64 67 65 INTEGER :: nqtrue ! number of tracers read from tracer.def, without higer order of moment 68 66 INTEGER :: iq, new_iq, iiq, jq, ierr 69 INTEGER, EXTERNAL :: lnblnk70 67 68 character(len=*),parameter :: modname="infotrac_init" 71 69 !----------------------------------------------------------------------- 72 70 ! Initialization : … … 113 111 nqtrue=4 ! Defaut value 114 112 END IF 113 ! For Earth, water vapour & liquid tracers are not in the physics 115 114 nbtr=nqtrue-2 116 115 ELSE … … 120 119 121 120 IF (nqtrue < 2) THEN 122 WRITE(lunout,*) 'nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'121 WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum' 123 122 CALL abort_gcm('infotrac_init','Not enough tracers',1) 124 123 END IF … … 134 133 nqtrue=1 ! Defaut value 135 134 END IF 135 ! Other planets (for now); we have the same number of tracers 136 ! in the dynamics than in the physics 136 137 nbtr=nqtrue 137 138 … … 179 180 END DO 180 181 CLOSE(90) 181 ELSE ! Without tracer.def 182 ELSE ! Without tracer.def, set default values (for Earth!) 183 if ((nqtrue==4).and.(planet_type=="earth")) then 182 184 hadv(1) = 14 183 185 vadv(1) = 14 … … 192 194 vadv(4) = 10 193 195 tnom_0(4) = 'PB' 196 else 197 ! Error message, we need a traceur.def file 198 write(lunout,*) trim(modname),& 199 ': Cannot set default tracer names!' 200 write(lunout,*) trim(modname),' Make a traceur.def file!!!' 201 CALL abort_gcm('infotrac_init','Need a traceur.def file!',1) 202 endif ! of if (nqtrue==4) 194 203 END IF 195 204 196 WRITE(lunout,*) 'Valeur de traceur.def :'197 WRITE(lunout,*) 'nombre de traceurs ',nqtrue205 WRITE(lunout,*) trim(modname),': Valeur de traceur.def :' 206 WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue 198 207 DO iq=1,nqtrue 199 208 WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq) … … 234 243 END IF 235 244 236 WRITE(lunout,*) 'Valeur de traceur.def :'237 WRITE(lunout,*) 'nombre de traceurs ',nqtrue245 WRITE(lunout,*) trim(modname),': Valeur de traceur.def :' 246 WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue 238 247 DO iq=1,nqtrue 239 248 WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq) … … 258 267 new_iq=new_iq+10 ! 9 tracers added 259 268 ELSE 260 WRITE(lunout,*) 'This choice of advection schema is not available',iq,hadv(iq),vadv(iq)269 WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq) 261 270 CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1) 262 271 END IF … … 268 277 nqtot = new_iq 269 278 270 WRITE(lunout,*) 'The choice of advection schema for one or more tracers'279 WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers' 271 280 WRITE(lunout,*) 'makes it necessary to add tracers' 272 WRITE(lunout,*) nqtrue,' is the number of true tracers'273 WRITE(lunout,*) nqtot, ' is the total number of tracers needed'281 WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers' 282 WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed' 274 283 275 284 ELSE … … 299 308 iadv(new_iq)=11 300 309 ELSE 301 WRITE(lunout,*)'This choice of advection schema is not available',iq,hadv(iq),vadv(iq) 310 WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq) 311 302 312 CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1) 303 313 END IF … … 317 327 new_iq=new_iq+1 318 328 iadv(new_iq)=-20 319 ttext(new_iq)= str2(1:lnblnk(str2))//txts(jq)320 tname(new_iq)= str1(1:lnblnk(str1))//txts(jq)329 ttext(new_iq)=trim(str2)//txts(jq) 330 tname(new_iq)=trim(str1)//txts(jq) 321 331 END DO 322 332 ELSE IF (iadv(new_iq)==30) THEN … … 324 334 new_iq=new_iq+1 325 335 iadv(new_iq)=-30 326 ttext(new_iq)= str2(1:lnblnk(str2))//txtp(jq)327 tname(new_iq)= str1(1:lnblnk(str1))//txtp(jq)336 ttext(new_iq)=trim(str2)//txtp(jq) 337 tname(new_iq)=trim(str1)//txtp(jq) 328 338 END DO 329 339 END IF … … 344 354 345 355 346 WRITE(lunout,*) 'Information stored in infotrac :'347 WRITE(lunout,*) 'iadv niadv tname ttext :'356 WRITE(lunout,*) trim(modname),': Information stored in infotrac :' 357 WRITE(lunout,*) trim(modname),': iadv niadv tname ttext :' 348 358 DO iq=1,nqtot 349 WRITE(lunout,*) iadv(iq),niadv(iq), tname(iq), ttext(iq) 359 WRITE(lunout,*) iadv(iq),niadv(iq),& 360 ' ',trim(tname(iq)),' ',trim(ttext(iq)) 350 361 END DO 351 362 … … 356 367 DO iq=1,nqtot 357 368 IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN 358 WRITE(lunout,*) 'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'369 WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ' 359 370 CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1) 360 371 ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN 361 WRITE(lunout,*) 'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'372 WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ' 362 373 CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1) 363 374 END IF -
trunk/libf/dyn3d/iniacademic.F
r1 r7 1 1 ! 2 ! $Id: iniacademic.F 14 37 2010-09-30 08:29:10Z emillour $2 ! $Id: iniacademic.F 1446 2010-10-22 09:27:25Z emillour $ 3 3 ! 4 4 c … … 8 8 USE filtreg_mod 9 9 USE infotrac, ONLY : nqtot 10 USE control_mod 10 USE control_mod, ONLY: day_step,planet_type 11 11 #ifdef CPP_IOIPSL 12 12 USE IOIPSL … … 95 95 ! 1. Initializations for Earth-like case 96 96 ! -------------------------------------- 97 if (planet_type=="earth") then98 97 c 99 98 ! initialize planet radius, rotation rate,... … … 128 127 if (.not.read_start) then 129 128 phis(:)=0. 130 q(:,:,1)=1.e-10 131 q(:,:,2)=1.e-15 132 q(:,:,3:nqtot)=0. 129 q(:,:,:)=0 133 130 CALL sw_case_williamson91_6(vcov,ucov,teta,masse,ps) 134 131 endif … … 138 135 ! initializations for the academic case 139 136 137 ! if (planet_type=="earth") then 138 140 139 ! 1. local parameters 141 140 ! by convention, winter is in the southern hemisphere … … 219 218 enddo 220 219 220 221 ! else 222 ! write(lunout,*)"iniacademic: planet types other than earth", 223 ! & " not implemented (yet)." 224 ! stop 225 ! endif ! of if (planet_type=="earth") 226 221 227 ! 3. Initialize fields (if necessary) 222 228 IF (.NOT. read_start) THEN … … 245 251 246 252 ! bulk initialization of tracers 247 do i=1,nqtot 248 if (i.eq.1) q(:,:,i)=1.e-10 249 if (i.eq.2) q(:,:,i)=1.e-15 250 if (i.gt.2) q(:,:,i)=0. 251 enddo 253 if (planet_type=="earth") then 254 ! Earth: first two tracers will be water 255 do i=1,nqtot 256 if (i.eq.1) q(:,:,i)=1.e-10 257 if (i.eq.2) q(:,:,i)=1.e-15 258 if (i.gt.2) q(:,:,i)=0. 259 enddo 260 else 261 q(:,:,:)=0 262 endif ! of if (planet_type=="earth") 252 263 253 264 ! add random perturbation to temperature … … 261 272 enddo 262 273 274 ! maintain periodicity in longitude 263 275 do l=1,llm 264 276 do ij=1,ip1jmp1,iip1 … … 267 279 enddo 268 280 269 c PRINT *,' Appel test_period avec tetarappel '270 c CALL test_period ( ucov,vcov,tetarappel,q,p,phis )271 c PRINT *,' Appel test_period avec teta '272 c CALL test_period ( ucov,vcov,teta,q,p,phis )273 274 ! initialize a traceur on one column275 ! j=jjp1*3/4276 ! i=iip1/2277 ! ij=(j-1)*iip1+i278 ! q(ij,:,3)=1.279 280 281 ENDIF ! of IF (.NOT. read_start) 281 282 endif ! of if (iflag_phys.eq.2) 282 283 283 else284 write(lunout,*)"iniacademic: planet types other than earth",285 & " not implemented (yet)."286 stop287 endif ! of if (planet_type=="earth")288 return289 284 END 290 285 c----------------------------------------------------------------------- -
trunk/libf/dyn3d/integrd.F
r1 r7 1 1 ! 2 ! $Id: integrd.F 14 03 2010-07-01 09:02:53Z fairhead$2 ! $Id: integrd.F 1446 2010-10-22 09:27:25Z emillour $ 3 3 ! 4 4 SUBROUTINE integrd … … 6 6 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis,finvmaold ) 7 7 8 USE control_mod8 use control_mod, only : planet_type 9 9 10 10 IMPLICIT NONE … … 81 81 CALL SCOPY(ip1jmp1*llm, masse, 1, massescr, 1) 82 82 83 DO 2ij = 1,ip1jmp183 DO ij = 1,ip1jmp1 84 84 pscr (ij) = ps(ij) 85 85 ps (ij) = psm1(ij) + dt * dp(ij) 86 2 CONTINUE86 ENDDO 87 87 c 88 88 DO ij = 1,ip1jmp1 … … 115 115 c ............ integration de ucov, vcov, h .............. 116 116 117 DO 10l = 1,llm118 119 DO 4ij = iip2,ip1jm120 uscr( ij ) = ucov( ij,l )121 ucov( ij,l ) = ucovm1( ij,l ) + dt * du( ij,l )122 4 CONTINUE123 124 DO 5ij = 1,ip1jm125 vscr( ij ) = vcov( ij,l )126 vcov( ij,l ) = vcovm1( ij,l ) + dt * dv( ij,l )127 5 CONTINUE128 129 DO 6ij = 1,ip1jmp1130 hscr( ij ) = teta(ij,l)131 teta ( ij,l ) = tetam1(ij,l) * massem1(ij,l) / masse(ij,l)132 $+ dt * dteta(ij,l) / masse(ij,l)133 6 CONTINUE117 DO l = 1,llm 118 119 DO ij = iip2,ip1jm 120 uscr( ij ) = ucov( ij,l ) 121 ucov( ij,l ) = ucovm1( ij,l ) + dt * du( ij,l ) 122 ENDDO 123 124 DO ij = 1,ip1jm 125 vscr( ij ) = vcov( ij,l ) 126 vcov( ij,l ) = vcovm1( ij,l ) + dt * dv( ij,l ) 127 ENDDO 128 129 DO ij = 1,ip1jmp1 130 hscr( ij ) = teta(ij,l) 131 teta ( ij,l ) = tetam1(ij,l) * massem1(ij,l) / masse(ij,l) 132 & + dt * dteta(ij,l) / masse(ij,l) 133 ENDDO 134 134 135 135 c .... Calcul de la valeur moyenne, unique aux poles pour teta ...... 136 136 c 137 137 c 138 DO ij = 1, iim138 DO ij = 1, iim 139 139 tppn(ij) = aire( ij ) * teta( ij ,l) 140 140 tpps(ij) = aire(ij+ip1jm) * teta(ij+ip1jm,l) 141 ENDDO141 ENDDO 142 142 tpn = SSUM(iim,tppn,1)/apoln 143 143 tps = SSUM(iim,tpps,1)/apols 144 144 145 DO ij = 1, iip1145 DO ij = 1, iip1 146 146 teta( ij ,l) = tpn 147 147 teta(ij+ip1jm,l) = tps 148 ENDDO149 c 150 151 IF(leapf) THEN148 ENDDO 149 c 150 151 IF(leapf) THEN 152 152 CALL SCOPY ( ip1jmp1, uscr(1), 1, ucovm1(1, l), 1 ) 153 153 CALL SCOPY ( ip1jm, vscr(1), 1, vcovm1(1, l), 1 ) 154 154 CALL SCOPY ( ip1jmp1, hscr(1), 1, tetam1(1, l), 1 ) 155 END IF156 157 10 CONTINUE155 END IF 156 157 ENDDO ! of DO l = 1,llm 158 158 159 159 … … 185 185 c$$$ ENDIF 186 186 187 187 if (planet_type.eq."earth") then 188 188 ! Earth-specific treatment of first 2 tracers (water) 189 190 189 DO l = 1, llm 190 DO ij = 1, ip1jmp1 191 191 deltap(ij,l) = p(ij,l) - p(ij,l+1) 192 ENDDO193 192 ENDDO 194 195 CALL qminimum( q, nq, deltap ) 196 endif ! of if (planet_type.eq."earth")193 ENDDO 194 195 CALL qminimum( q, nq, deltap ) 197 196 198 197 c … … 200 199 c 201 200 202 DO iq = 1, nq201 DO iq = 1, nq 203 202 DO l = 1, llm 204 203 … … 216 215 217 216 ENDDO 218 ENDDO 219 220 221 CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 ) 217 ENDDO 218 219 220 CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 ) 221 222 endif ! of if (planet_type.eq."earth") 222 223 c 223 224 c 224 225 c ..... FIN de l'integration de q ....... 225 226 15 continue227 226 228 227 c ................................................................. -
trunk/libf/dyn3d/leapfrog.F
r6 r7 1 1 ! 2 ! $Id: leapfrog.F 14 37 2010-09-30 08:29:10Z emillour $2 ! $Id: leapfrog.F 1446 2010-10-22 09:27:25Z emillour $ 3 3 ! 4 4 c … … 225 225 c -------------------------------------------------- 226 226 227 dq =0.227 dq(:,:,:)=0. 228 228 CALL pression ( ip1jmp1, ap, bp, ps, p ) 229 229 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) … … 269 269 CALL SCOPY ( ijp1llm, masse, 1, finvmaold, 1 ) 270 270 CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 ) 271 272 ! Ehouarn: what is this for? zqmin & zqmax are not used anyway ...273 ! call minmax(ijp1llm,q(:,:,3),zqmin,zqmax)274 271 275 272 2 CONTINUE … … 470 467 ! Sponge layer (if any) 471 468 IF (ok_strato) THEN 469 dutop(:,:)=0. 470 dvtop(:,:)=0. 471 dtetatop(:,:)=0. 472 dqtop(:,:,:)=0. 473 dptop(:)=0. 472 474 CALL top_bound(vcov,ucov,teta,masse,dutop,dvtop,dtetatop) 473 475 CALL addfi( dtvr, leapf, forward , -
trunk/libf/dyn3d/limit_netcdf.F90
r1 r7 1 1 ! 2 ! $Id: limit_netcdf.F90 14 25 2010-09-02 13:45:23Z lguez$2 ! $Id: limit_netcdf.F90 1441 2010-10-13 13:06:56Z emillour $ 3 3 !------------------------------------------------------------------------------- 4 4 ! … … 97 97 kappa = 0.2857143 98 98 cpp = 1004.70885 99 dtvr = daysec/ FLOAT(day_step)99 dtvr = daysec/REAL(day_step) 100 100 CALL inigeom 101 101 … … 265 265 266 266 DEALLOCATE(pctsrf_t,phy_sst,phy_bil,phy_alb,phy_rug) 267 #endif268 ! of #ifdef CPP_EARTH269 267 270 268 … … 592 590 593 591 !--- Mid-months times 594 mid_months(1)=0.5* FLOAT(mnth(1))592 mid_months(1)=0.5*REAL(mnth(1)) 595 593 DO k=2,nm 596 mid_months(k)=mid_months(k-1)+0.5* FLOAT(mnth(k-1)+mnth(k))594 mid_months(k)=mid_months(k-1)+0.5*REAL(mnth(k-1)+mnth(k)) 597 595 END DO 598 596 … … 626 624 !------------------------------------------------------------------------------- 627 625 626 #endif 627 ! of #ifdef CPP_EARTH 628 628 629 629 END SUBROUTINE limit_netcdf
Note: See TracChangeset
for help on using the changeset viewer.