Changeset 52 for trunk/libf/dyn3dpar
- Timestamp:
- Jan 31, 2011, 12:42:42 AM (14 years ago)
- Location:
- trunk/libf/dyn3dpar
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/libf/dyn3dpar/calfis_p.F
r8 r52 288 288 ALLOCATE(flxwfi(klon,llm)) 289 289 ! ADAPTATION GCM POUR CP(T) 290 ALLOCATE(zteta(klon,llm) 290 ALLOCATE(zteta(klon,llm)) 291 291 ALLOCATE(zpk(klon,llm)) 292 292 c$OMP END MASTER -
trunk/libf/dyn3dpar/comconst.h
r8 r52 11 11 & ,dissip_factz,dissip_deltaz,dissip_zref & 12 12 & ,tau_top_bound, & 13 & daylen,year_day,molmass 13 & daylen,year_day,molmass, ihf 14 14 COMMON/cpdetvenus/nu_venus,t0_venus 15 15 … … 36 36 37 37 REAL nu_venus,t0_venus ! coeffs needed for Cp(T), Venus atmosphere 38 REAL ihf ! (W/m2) intrinsic heat flux for giant planets 38 39 39 40 -
trunk/libf/dyn3dpar/conf_planete.F90
r1 r52 64 64 CALL getin('omeg',omeg) 65 65 66 ! Intrinsic heat flux [default is none] 67 ! Aymeric -- for giant planets 68 ! [matters only if planet_type="giant"] 69 ihf = 0. 70 CALL getin('ihf',ihf) 71 72 73 66 74 END SUBROUTINE conf_planete -
trunk/libf/dyn3dpar/gcm.F
r8 r52 59 59 c Declarations: 60 60 c ------------- 61 61 62 #include "dimensions.h" 62 63 #include "paramet.h" … … 67 68 #include "logic.h" 68 69 #include "temps.h" 70 !!!!!!!!!!!#include "control.h" 69 71 #include "ener.h" 70 72 #include "description.h" … … 73 75 #include "iniprint.h" 74 76 #include "tracstoke.h" 75 76 77 #ifdef INCA 77 78 ! Only INCA needs these informations (from the Earth's physics) 78 79 #include "indicesol.h" 79 80 #endif 80 81 81 INTEGER longcles 82 82 PARAMETER ( longcles = 20 ) … … 93 93 REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants 94 94 REAL teta(ip1jmp1,llm) ! temperature potentielle 95 REAL, ALLOCATABLE, DIMENSION(:,:,:) :: q! champs advectes95 REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes 96 96 REAL ps(ip1jmp1) ! pression au sol 97 97 c REAL p (ip1jmp1,llmp1 ) ! pression aux interfac.des couches … … 219 219 #endif 220 220 ! endif ! of if (planet_type.eq."earth") 221 221 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 222 c 222 223 c Initialisations pour Cp(T) Venus 223 224 call ini_cpdet 224 225 c 225 226 c----------------------------------------------------------------------- 226 227 c Choix du calendrier … … 244 245 endif 245 246 #endif 247 c----------------------------------------------------------------------- 246 248 247 249 IF (config_inca /= 'none') THEN … … 289 291 & teta,q,masse,ps,phis, time_0) 290 292 endif ! of if (planet_type.eq."mars") 291 293 292 294 c write(73,*) 'ucov',ucov 293 295 c write(74,*) 'vcov',vcov … … 304 306 CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0) 305 307 endif 308 306 309 307 310 c----------------------------------------------------------------------- … … 350 353 write(lunout,*)' Pas de remise a zero' 351 354 ENDIF 355 352 356 c if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then 353 357 c write(lunout,*) … … 432 436 c Initialisation de la physique : 433 437 c ------------------------------- 434 IF (call_iniphys.and.iflag_phys.eq.1) THEN 438 439 IF (call_iniphys.and.(iflag_phys.eq.1)) THEN 435 440 latfi(1)=rlatu(1) 436 441 lonfi(1)=0. … … 450 455 zcvfi(ngridmx) = cv(ip1jm-iim) 451 456 CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi) 452 453 457 WRITE(lunout,*) 454 458 . 'GCM: WARNING!!! vitesse verticale nulle dans la physique' 459 455 460 ! Initialisation de la physique: pose probleme quand on tourne 456 461 ! SANS physique, car iniphysiq.F est dans le repertoire phy[]... … … 462 467 call_iniphys=.false. 463 468 ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1)) 464 469 !#endif 465 470 466 471 c----------------------------------------------------------------------- … … 508 513 IF (mpi_rank==0) then 509 514 if (ok_dyn_ins) then 510 ! initialize output file for instantaneous outputs 511 ! t_ops = iecri * daysec ! do operations every t_ops 512 t_ops =((1.0*iecri)/day_step) * daysec 513 t_wrt = daysec ! iecri * daysec ! write output every t_wrt 514 t_wrt = daysec ! iecri * daysec ! write output every t_wrt 515 CALL inithist(day_ref,annee_ref,time_step, 515 ! initialize output file for instantaneous outputs 516 ! t_ops = iecri * daysec ! do operations every t_ops 517 t_ops =((1.0*iecri)/day_step) * daysec 518 t_wrt = daysec ! iecri * daysec ! write output every t_wrt 519 CALL inithist(day_ref,annee_ref,time_step, 516 520 & t_ops,t_wrt) 517 521 endif -
trunk/libf/dyn3dpar/iniacademic.F
r7 r52 96 96 ! -------------------------------------- 97 97 c 98 99 print *, 'This is iniacademic' 100 98 101 ! initialize planet radius, rotation rate,... 99 102 call conf_planete … … 155 158 teta0=315. ! mean Teta (S.H. 315K) 156 159 CALL getin('teta0',teta0) 160 print *, 'iniacademic - teta0 ', teta0 161 print *, 'iniacademic - rad ', rad 157 162 ttp=200. ! Tropopause temperature (S.H. 200K) 158 163 CALL getin('ttp',ttp) … … 200 205 tetajl(j,l)=teta0-delt_y*ddsin*ddsin+eps*ddsin 201 206 & -delt_z*(1.-ddsin*ddsin)*log(zsig) 207 !! Aymeric -- tests particuliers 208 if (planet_type=="giant") then 209 tetajl(j,l)=teta0+(delt_y* 210 & ((sin(rlatu(j)*3.14159*eps+0.0001))**2) 211 & / ((rlatu(j)*3.14159*eps+0.0001)**2)) 212 & -delt_z*log(zsig) 213 !!! ddsin=sin(2.5*3.14159*rlatu(j)) 214 !!! tetajl(j,l)=teta0-delt_y*ddsin*ddsin 215 !!!! & -delt_z*(1.-ddsin*ddsin)*log(zsig) 216 endif 202 217 ! Profil stratospherique isotherme (+vortex) 203 218 w_pv=(1.-tanh((rlatu(j)-phi_pv)/dphi_pv))/2. … … 217 232 enddo 218 233 enddo 234 PRINT *, 'iniacademic - check',tetajl(:,int(llm/2)),rlatu(:) 219 235 220 236 -
trunk/libf/dyn3dpar/leapfrog_p.F
r8 r52 117 117 REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: dqfi 118 118 119 !! Aymeric -- cp(T) comme dans leapfrog.F, SAVE OK ??? 120 REAL,SAVE :: duspg(ip1jmp1,llm) ! for bilan_dyn 121 122 119 123 c variables pour le fichier histoire 120 124 REAL dtav ! intervalle de temps elementaire … … 177 181 178 182 logical , parameter :: flag_verif = .false. 179 183 184 ! for CP(T) -- Aymeric 185 real :: dtec 186 real,external :: cpdet 187 real,save :: ztetaec(ip1jmp1,llm) !!SAVE ??? 188 180 189 c declaration liees au parallelisme 181 190 INTEGER :: ierr … … 560 569 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 561 570 do l=1,llm 562 tsurpk(ijb:ije,l lm)=cpp*temp(ijb:ije,llm)/pk(ijb:ije,llm)571 tsurpk(ijb:ije,l)=cpp*temp(ijb:ije,l)/pk(ijb:ije,l) 563 572 enddo 564 573 !$OMP END DO … … 999 1008 enddo ! of do l=1,llm 1000 1009 !$OMP END DO 1010 1011 if (planet_type.eq."giant") then 1012 ! Intrinsic heat flux 1013 ! Aymeric -- for giant planets 1014 if (ihf .gt. 1.e-6) then 1015 !print *, '**** INTRINSIC HEAT FLUX ****', ihf 1016 teta(ijb:ije,1) = teta(ijb:ije,1) 1017 & + dtvr * aire(ijb:ije) * ihf / cpp / masse(ijb:ije,1) 1018 !print *, '**** d teta ' 1019 !print *, dtvr * aire(ijb:ije) * ihf / cpp / masse(ijb:ije,1) 1020 endif 1021 endif 1001 1022 1002 1023 call Register_Hallo(ucov,ip1jmp1,llm,0,1,1,0,Request_Physic) … … 1463 1484 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 1464 1485 do l=1,llm 1465 tsurpk(ijb:ije,l lm)=cpp*temp(ijb:ije,llm)/pk(ijb:ije,llm)1486 tsurpk(ijb:ije,l)=cpp*temp(ijb:ije,l)/pk(ijb:ije,l) 1466 1487 enddo 1467 1488 !$OMP END DO … … 1685 1706 ije=ij_end 1686 1707 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 1687 do l=1,llm 1688 tsurpk(ijb:ije,l lm)=cpp*temp(ijb:ije,llm)/1689 & pk(ijb:ije,l lm)1708 do l=1,llm 1709 tsurpk(ijb:ije,l)=cpp*temp(ijb:ije,l)/ 1710 & pk(ijb:ije,l) 1690 1711 enddo 1691 1712 !$OMP END DO
Note: See TracChangeset
for help on using the changeset viewer.