Changeset 1673 for LMDZ5/trunk/libf/dyn3dmem/leapfrog_loc.F
- Timestamp:
- Oct 27, 2012, 4:23:07 PM (12 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/dyn3dmem/leapfrog_loc.F
r1659 r1673 1 1 ! 2 ! $Id : leapfrog_p.F 1299 2010-01-20 14:27:21Z fairhead$2 ! $Id$ 3 3 ! 4 4 c … … 119 119 120 120 c tendances physiques 121 !REAL,SAVE,ALLOCATABLE :: dvfi(:,:),dufi(:,:)122 !REAL,SAVE,ALLOCATABLE :: dtetafi(:,:)123 !REAL,SAVE,ALLOCATABLE :: dpfi(:)124 !REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: dqfi121 REAL,SAVE,ALLOCATABLE :: dvfi(:,:),dufi(:,:) 122 REAL,SAVE,ALLOCATABLE :: dtetafi(:,:) 123 REAL,SAVE,ALLOCATABLE :: dpfi(:) 124 REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: dqfi 125 125 126 126 c variables pour le fichier histoire … … 150 150 REAL :: secondes 151 151 152 logical :: physic 152 153 LOGICAL first,callinigrads 153 154 … … 174 175 175 176 character*80 dynhist_file, dynhistave_file 176 character *20 modname177 character(len=*),parameter :: modname="leapfrog_loc" 177 178 character*80 abort_message 178 179 … … 195 196 196 197 INTEGER :: true_itau 197 LOGICAL :: verbose=.true.198 198 INTEGER :: iapptrac 199 199 INTEGER :: AdjustCount … … 215 215 itaufin = nday*day_step 216 216 itaufinp1 = itaufin +1 217 modname="leapfrog_p"218 217 219 218 itau = 0 219 physic=.true. 220 if (iflag_phys==0.or.iflag_phys==2) physic=.false. 220 221 CALL init_nan 221 222 CALL leapfrog_allocate … … 252 253 ! ALLOCATE(dvdis(ijb_v:ije_v,llm),dudis(ijb_u:ije_u,llm)) 253 254 ! ALLOCATE(dtetadis(ijb_u:ije_u,llm)) 254 !ALLOCATE(dvfi(ijb_v:ije_v,llm),dufi(ijb_u:ije_u,llm))255 !ALLOCATE(dtetafi(ijb_u:ije_u,llm))256 !ALLOCATE(dpfi(ijb_u:ije_u))255 ALLOCATE(dvfi(ijb_v:ije_v,llm),dufi(ijb_u:ije_u,llm)) 256 ALLOCATE(dtetafi(ijb_u:ije_u,llm)) 257 ALLOCATE(dpfi(ijb_u:ije_u)) 257 258 ! ALLOCATE(dq(ijb_u:ije_u,llm,nqtot)) 258 !ALLOCATE(dqfi(ijb_u:ije_u,llm,nqtot))259 ALLOCATE(dqfi(ijb_u:ije_u,llm,nqtot)) 259 260 ! ALLOCATE(dqfi_tmp(iip1,llm,nqtot)) 260 261 ! ALLOCATE(finvmaold(ijb_u:ije_u,llm)) … … 277 278 278 279 c$OMP MASTER 279 dq =0.280 dq(:,:,:)=0. 280 281 CALL pression ( ijnb_u, ap, bp, ps, p ) 281 282 c$OMP END MASTER 283 if (pressure_exner) then 282 284 CALL exner_hyb_loc( ijnb_u, ps, p,alpha,beta, pks, pk, pkf) 283 285 else 286 CALL exner_milieu_loc( ijnb_u, ps, p, beta, pks, pk, pkf ) 287 endif 284 288 c----------------------------------------------------------------------- 285 289 c Debut de l'integration temporelle: … … 287 291 c et du parallelisme !! 288 292 289 1 CONTINUE 290 291 jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec) 292 jH_cur = jH_ref + & 293 & (itau * dtvr / daysec - int(itau * dtvr / daysec)) 293 1 CONTINUE ! Matsuno Forward step begins here 294 295 jD_cur = jD_ref + day_ini - day_ref + & 296 & itau/day_step 297 jH_cur = jH_ref + start_time + & 298 & mod(itau,day_step)/float(day_step) 299 if (jH_cur > 1.0 ) then 300 jD_cur = jD_cur +1. 301 jH_cur = jH_cur -1. 302 endif 303 294 304 295 305 #ifdef CPP_IOIPSL … … 323 333 psm1= ps 324 334 325 finvmaold = masse 326 c$OMP END MASTER 327 c$OMP BARRIER 328 CALL filtreg_p ( finvmaold ,jjb_u,jje_u,jjb_u,jje_u,jjp1, llm, 329 & -2,2, .TRUE., 1 ) 335 ! Ehouarn: finvmaold is actually not used 336 ! finvmaold = masse 337 c$OMP END MASTER 338 c$OMP BARRIER 339 ! CALL filtreg_p ( finvmaold ,jjb_u,jje_u,jjb_u,jje_u,jjp1, llm, 340 ! & -2,2, .TRUE., 1 ) 330 341 else 331 342 ! Save fields obtained at previous time step as '...m1' … … 343 354 tetam1 (ijb:ije,l) = teta (ijb:ije,l) 344 355 massem1 (ijb:ije,l) = masse (ijb:ije,l) 345 finvmaold(ijb:ije,l)=masse(ijb:ije,l)356 ! finvmaold(ijb:ije,l)=masse(ijb:ije,l) 346 357 347 358 if (pole_sud) ije=ij_end-iip1 … … 353 364 354 365 355 CALL filtreg_p(finvmaold ,jjb_u,jje_u,jj_begin,jj_end,jjp1, 356 . llm, -2,2, .TRUE., 1 ) 366 ! Ehouarn: finvmaold not used 367 ! CALL filtreg_p(finvmaold ,jjb_u,jje_u,jj_begin,jj_end,jjp1, 368 ! . llm, -2,2, .TRUE., 1 ) 357 369 358 370 endif ! of if (FirstCaldyn) … … 370 382 cym call minmax(ijp1llm,q(:,:,3),zqmin,zqmax) 371 383 372 2 CONTINUE 384 2 CONTINUE ! Matsuno backward or leapfrog step begins here 373 385 374 386 c$OMP MASTER … … 399 411 ! Purely Matsuno time stepping 400 412 IF( MOD(itau,iconser) .EQ.0.AND. forward ) conser = .TRUE. 401 IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE. 413 IF( MOD(itau,dissip_period ).EQ.0.AND..NOT.forward ) 414 s apdiss = .TRUE. 402 415 IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward 403 s .and. iflag_phys.EQ.1) apphys = .TRUE.416 s .and. physic ) apphys = .TRUE. 404 417 ELSE 405 418 ! Leapfrog/Matsuno time stepping 406 419 IF( MOD(itau ,iconser) .EQ. 0 ) conser = .TRUE. 407 IF( MOD(itau+1,idissip) .EQ. 0 ) apdiss = .TRUE. 408 IF( MOD(itau+1,iphysiq).EQ.0.AND.iflag_phys.EQ.1) apphys=.TRUE. 420 IF( MOD(itau+1,dissip_period).EQ.0 .AND. .NOT. forward ) 421 s apdiss = .TRUE. 422 IF( MOD(itau+1,iphysiq).EQ.0.AND.physic) apphys=.TRUE. 409 423 END IF 410 424 … … 450 464 c$OMP MASTER 451 465 call allgather_timer_average 452 verbose=.TRUE. 453 if ( Verbose) then466 467 if (prt_level > 9) then 454 468 455 469 print *,'*********************************' … … 622 636 call start_timer(timer_caldyn) 623 637 638 ! compute geopotential phi() 624 639 CALL geopot_loc ( ip1jmp1, teta , pk , pks, phis , phi ) 625 640 … … 697 712 698 713 CALL integrd_loc ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 , 699 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,700 $ finvmaold )714 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis) 715 ! $ finvmaold ) 701 716 702 717 ! CALL FTRACE_REGION_END("integrd") … … 1081 1096 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 1082 1097 do l=1,llm 1083 teta(ijb:ije,l)=teta(ijb:ije,l) 1084 & -iphysiq*dtvr*(teta(ijb:ije,l)-tetarappel(ijb:ije,l))/taurappel 1098 teta(ijb:ije,l)=teta(ijb:ije,l) -dtvr* 1099 & (teta(ijb:ije,l)-tetarappel(ijb:ije,l))* 1100 & (knewt_g+knewt_t(l)*clat4(ijb:ije)) 1085 1101 enddo 1086 1102 !$OMP END DO 1103 1104 !$OMP MASTER 1105 if (planet_type.eq."giant") then 1106 ! add an intrinsic heat flux at the base of the atmosphere 1107 teta(ijb:ije,1) = teta(ijb:ije,1) 1108 & + dtvr * aire(ijb:ije) * ihf / cpp / masse(ijb:ije,1) 1109 endif 1110 !$OMP END MASTER 1111 !$OMP BARRIER 1112 1087 1113 1088 1114 call Register_Hallo_u(ucov,llm,0,1,1,0,Request_Physic) … … 1092 1118 call WaitRequest(Request_Physic) 1093 1119 c$OMP BARRIER 1094 call friction_loc(ucov,vcov, iphysiq*dtvr)1120 call friction_loc(ucov,vcov,dtvr) 1095 1121 !$OMP BARRIER 1122 1123 ! Sponge layer (if any) 1124 IF (ok_strato) THEN 1125 ! set dufi,dvfi,... to zero 1126 ijb=ij_begin 1127 ije=ij_end 1128 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 1129 do l=1,llm 1130 dufi(ijb:ije,l)=0 1131 dtetafi(ijb:ije,l)=0 1132 dqfi(ijb:ije,l,1:nqtot)=0 1133 enddo 1134 !$OMP END DO 1135 !$OMP MASTER 1136 dpfi(ijb:ije)=0 1137 !$OMP END MASTER 1138 ijb=ij_begin 1139 ije=ij_end 1140 if (pole_sud) ije=ije-iip1 1141 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 1142 do l=1,llm 1143 dvfi(ijb:ije,l)=0 1144 enddo 1145 !$OMP END DO 1146 1147 CALL top_bound_loc(vcov,ucov,teta,masse,dufi,dvfi,dtetafi) 1148 CALL addfi_loc( dtvr, leapf, forward , 1149 $ ucov, vcov, teta , q ,ps , 1150 $ dufi, dvfi, dtetafi , dqfi ,dpfi ) 1151 !$OMP BARRIER 1152 ENDIF ! of IF (ok_strato) 1096 1153 ENDIF ! of IF(iflag_phys.EQ.2) 1097 1154 … … 1099 1156 CALL pression_loc ( ip1jmp1, ap, bp, ps, p ) 1100 1157 c$OMP BARRIER 1101 CALL exner_hyb_loc( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 1158 if (pressure_exner) then 1159 CALL exner_hyb_loc( ijnb_u, ps, p,alpha,beta, pks, pk, pkf ) 1160 else 1161 CALL exner_milieu_loc( ijnb_u, ps, p, beta, pks, pk, pkf ) 1162 endif 1102 1163 c$OMP BARRIER 1103 1164 … … 1496 1557 c$OMP BARRIER 1497 1558 1498 if (planet_type.eq."earth") then1559 ! if (planet_type.eq."earth") then 1499 1560 ! Write an Earth-format restart file 1500 1561 CALL dynredem1_loc("restart.nc",0.0, 1501 1562 & vcov,ucov,teta,q,masse,ps) 1502 endif ! of if (planet_type.eq."earth")1563 ! endif ! of if (planet_type.eq."earth") 1503 1564 1504 1565 ! CLOSE(99) … … 1608 1669 1609 1670 IF(itau.EQ.itaufin) THEN 1610 if (planet_type.eq."earth") then1671 ! if (planet_type.eq."earth") then 1611 1672 CALL dynredem1_loc("restart.nc",0.0, 1612 1673 . vcov,ucov,teta,q,masse,ps) 1613 1674 ! endif ! of if (planet_type.eq."earth") 1614 1675 ENDIF ! of IF(itau.EQ.itaufin) 1615 1676
Note: See TracChangeset
for help on using the changeset viewer.