Changeset 124 for trunk/libf/dyn3d
- Timestamp:
- May 19, 2011, 5:05:39 PM (14 years ago)
- Location:
- trunk/libf/dyn3d
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/libf/dyn3d/comvert.h
r109 r124 7 7 COMMON/comvert/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm), & 8 8 & pa,preff,nivsigs(llm),nivsig(llm+1), & 9 & aps(llm),bps(llm) 9 & aps(llm),bps(llm),scaleheight 10 10 11 11 REAL ap,bp,presnivs,dpres,pa,preff,nivsigs,nivsig,aps,bps 12 real scaleheight ! atmospheric (reference) scale height (km) 12 13 13 14 !----------------------------------------------------------------------- -
trunk/libf/dyn3d/disvert_noterre.F
r110 r124 4 4 c Nouvelle version 100% Mars !! 5 5 c On l'utilise aussi pour Venus et Titan, legerment modifiee. 6 7 #ifdef CPP_IOIPSL 8 use IOIPSL 9 #else 10 ! if not using IOIPSL, we still need to use (a local version of) getin 11 use ioipsl_getincom 12 #endif 6 13 7 14 IMPLICIT NONE … … 12 19 #include "comconst.h" 13 20 #include "logic.h" 21 #include "iniprint.h" 14 22 c 15 23 c======================================================================= … … 24 32 INTEGER l,ll 25 33 REAL snorm 26 REAL alpha,beta,gama,delta,deltaz,h,quoi,quand 34 REAL alpha,beta,gama,delta,deltaz 35 real quoi,quand 27 36 REAL zsig(llm),sig(llm+1) 28 37 INTEGER np,ierr … … 44 53 c----------------------------------------------------------------------- 45 54 c 55 ! Initializations: 46 56 pi=2.*ASIN(1.) 57 58 hybrid=.true. ! default value for hybrid (ie: use hybrid coordinates) 59 CALL getin('hybrid',hybrid) 60 write(lunout,*)'disvert_noterre: hybrid=',hybrid 47 61 48 62 ! Ouverture possible de fichiers typiquement E.T. … … 67 81 c <-> energie cinetique, d'apres la note de Frederic Hourdin... 68 82 69 PRINT*,'*****************************'70 PRINT*,'WARNING Lecture deesasig.def'71 PRINT*,'*****************************'72 READ(99,*) h83 write(lunout,*)'*****************************' 84 write(lunout,*)'WARNING reading esasig.def' 85 write(lunout,*)'*****************************' 86 READ(99,*) scaleheight 73 87 READ(99,*) dz0 74 88 READ(99,*) dz1 … … 76 90 CLOSE(99) 77 91 78 dz0=dz0/ h79 dz1=dz1/ h92 dz0=dz0/scaleheight 93 dz1=dz1/scaleheight 80 94 81 95 sig1=(1.-dz1)/tanh(.5*(llm-1)/nhaut) … … 116 130 117 131 ELSE IF(ierr4.eq.0) then 118 PRINT*,'****************************'119 PRINT*,'Lecture dez2sig.def'120 PRINT*,'****************************'121 122 READ(99,*) h132 write(lunout,*)'****************************' 133 write(lunout,*)'Reading z2sig.def' 134 write(lunout,*)'****************************' 135 136 READ(99,*) scaleheight 123 137 do l=1,llm 124 138 read(99,*) zsig(l) … … 128 142 sig(1) =1 129 143 do l=2,llm 130 sig(l) = 0.5 * ( exp(-zsig(l)/h) + exp(-zsig(l-1)/h) ) 144 sig(l) = 0.5 * ( exp(-zsig(l)/scaleheight) + 145 & exp(-zsig(l-1)/scaleheight) ) 131 146 end do 132 147 sig(llm+1) =0 … … 134 149 c----------------------------------------------------------------------- 135 150 ELSE 136 write( *,*) 'didn t you forget something ??? '137 write( *,*) 'We need the file z2sig.def ! (OR esasig.def)'151 write(lunout,*) 'didn t you forget something ??? ' 152 write(lunout,*) 'We need file z2sig.def ! (OR esasig.def)' 138 153 stop 139 154 ENDIF … … 156 171 c----------------------------------------------------------------------- 157 172 c 158 c se trouvait dans Titan... Verifier... 159 c h = 40. 160 161 if (1.eq.1) then ! toujours hybrides 162 write(*,*) "*******************************" 163 write(*,*) "Systeme en coordonnees hybrides" 164 write(*,*) 173 174 if (hybrid) then ! use hybrid coordinates 175 write(lunout,*) "*********************************" 176 write(lunout,*) "Using hybrid vertical coordinates" 177 write(lunout,*) 165 178 c Coordonnees hybrides avec mod 166 179 DO l = 1, llm … … 172 185 bp(llmp1) = 0. 173 186 ap(llmp1) = 0. 174 else 175 write( *,*) "****************************"176 write( *,*) "Systeme en coordonnees sigma"177 write( *,*)187 else ! use sigma coordinates 188 write(lunout,*) "********************************" 189 write(lunout,*) "Using sigma vertical coordinates" 190 write(lunout,*) 178 191 c Pour ne pas passer en coordonnees hybrides 179 192 DO l = 1, llm … … 186 199 bp(llmp1) = 0. 187 200 188 PRINT *,' BP '189 PRINT *,bp190 PRINT *,' AP '191 PRINT *,ap201 write(lunout,*)' BP ' 202 write(lunout,*) bp 203 write(lunout,*)' AP ' 204 write(lunout,*) ap 192 205 193 206 c Calcul au milieu des couches : … … 197 210 c (on met la meme distance (en log pression) entre P(llm) 198 211 c et P(llm -1) qu'entre P(llm-1) et P(llm-2) ) est 199 c Specifique. Ce choix est spécifié ici ET dans exner_ hyb.F212 c Specifique. Ce choix est spécifié ici ET dans exner_milieu.F 200 213 201 214 DO l = 1, llm-1 … … 204 217 ENDDO 205 218 206 cif (hybrid) then219 if (hybrid) then 207 220 aps(llm) = aps(llm-1)**2 / aps(llm-2) 208 221 bps(llm) = 0.5*(bp(llm) + bp(llm+1)) 209 celse210 cbps(llm) = bps(llm-1)**2 / bps(llm-2)211 caps(llm) = 0.212 cend if213 214 PRINT *,' BPs '215 PRINT *,bps216 PRINT *,' APs'217 PRINT *,aps222 else 223 bps(llm) = bps(llm-1)**2 / bps(llm-2) 224 aps(llm) = 0. 225 end if 226 227 write(lunout,*)' BPs ' 228 write(lunout,*) bps 229 write(lunout,*)' APs' 230 write(lunout,*) aps 218 231 219 232 DO l = 1, llm 220 233 presnivs(l) = aps(l)+bps(l)*preff 221 pseudoalt(l) = - h*log(presnivs(l)/preff)234 pseudoalt(l) = -scaleheight*log(presnivs(l)/preff) 222 235 ENDDO 223 236 224 PRINT *,' PRESNIVS' 225 PRINT *,presnivs 226 PRINT *,'Pseudo altitude des Presnivs : (avec H = ',h,' km)' 227 PRINT *,pseudoalt 237 write(lunout,*)' PRESNIVS' 238 write(lunout,*)presnivs 239 write(lunout,*)'Pseudo altitude of Presnivs : (for a scale ', 240 & 'height of ',scaleheight,' km)' 241 write(lunout,*)pseudoalt 228 242 229 243 c -------------------------------------------------- … … 232 246 c -------------------------------------------------- 233 247 c open (53,file='testhybrid.tab') 234 c h=15.5248 c scaleheight=15.5 235 249 c do iz=0,34 236 250 c z = -5 + min(iz,34-iz) 237 251 c approximation of scale height for Venus 238 c h= 15.5 - z/55.*10.239 c ps = preff*exp(-z/ h)240 c zsig(1)= - h*log((aps(1) + bps(1)*ps)/preff)252 c scaleheight = 15.5 - z/55.*10. 253 c ps = preff*exp(-z/scaleheight) 254 c zsig(1)= -scaleheight*log((aps(1) + bps(1)*ps)/preff) 241 255 c do l=2,llm 242 256 c approximation of scale height for Venus 243 257 c if (zsig(l-1).le.55.) then 244 c h= 15.5 - zsig(l-1)/55.*10.258 c scaleheight = 15.5 - zsig(l-1)/55.*10. 245 259 c else 246 c h= 5.5 - (zsig(l-1)-55.)/35.*2.260 c scaleheight = 5.5 - (zsig(l-1)-55.)/35.*2. 247 261 c endif 248 c zsig(l)= zsig(l-1)- h*262 c zsig(l)= zsig(l-1)-scaleheight* 249 263 c . log((aps(l) + bps(l)*ps)/(aps(l-1) + bps(l-1)*ps)) 250 264 c end do -
trunk/libf/dyn3d/exner_milieu.F
r109 r124 1 ! 2 ! $Id $ 3 ! 1 4 SUBROUTINE exner_milieu ( ngrid, ps, p,beta, pks, pk, pkf ) 2 5 c … … 44 47 REAL xpn, xps 45 48 REAL SSUM 46 EXTERNAL filtreg, SSUM 49 EXTERNAL SSUM 50 51 if (llm.eq.1) then 52 ! Specific behaviour for Shallow Water (1 vertical layer) case 53 54 ! Sanity checks 55 if (kappa.ne.1) then 56 call abort_gcm("exner_hyb", 57 & "kappa!=1 , but running in Shallow Water mode!!",42) 58 endif 59 if (cpp.ne.r) then 60 call abort_gcm("exner_hyb", 61 & "cpp!=r , but running in Shallow Water mode!!",42) 62 endif 63 64 ! Compute pks(:),pk(:),pkf(:) 65 66 DO ij = 1, ngrid 67 pks(ij) = (cpp/preff) * ps(ij) 68 pk(ij,1) = .5*pks(ij) 69 ENDDO 70 71 CALL SCOPY ( ngrid * llm, pk, 1, pkf, 1 ) 72 CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 ) 73 74 ! our work is done, exit routine 75 return 76 endif ! of if (llm.eq.1) 77 47 78 48 79 c ------------- -
trunk/libf/dyn3d/iniacademic.F90
r66 r124 207 207 enddo 208 208 enddo 209 write(lunout,*) 'Iniacademic - check',tetajl(:,int(llm/2)),rlatu(:)209 ! write(lunout,*) 'Iniacademic - check',tetajl(:,int(llm/2)),rlatu(:) 210 210 211 211 ! 3. Initialize fields (if necessary) … … 217 217 218 218 CALL pression ( ip1jmp1, ap, bp, ps, p ) 219 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 219 if (planet_type=="earth") then 220 CALL exner_hyb(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf) 221 else 222 call exner_milieu(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf) 223 endif 220 224 CALL massdair(p,masse) 221 225 -
trunk/libf/dyn3d/logic.h
r119 r124 3 3 ! 4 4 ! 5 ! 5 ! NB: keep items of different kinds in seperate common blocs to avoid 6 ! "misaligned commons" issues 6 7 !----------------------------------------------------------------------- 7 8 ! INCLUDE 'logic.h' 8 9 9 COMMON/logic / purmats,iflag_phys,forward,leapf,apphys,&10 COMMON/logicl/ purmats,forward,leapf,apphys, & 10 11 & statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus & 11 12 & ,read_start,ok_guide,ok_strato,ok_gradsfile & 12 & ,ok_limit,ok_etat0, iflag_trac13 & ,ok_limit,ok_etat0,hybrid 13 14 15 COMMON/logici/ iflag_phys,iflag_trac 16 14 17 LOGICAL purmats,forward,leapf,apphys,statcl,conser, & 15 18 & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus & 16 19 & ,read_start,ok_guide,ok_strato,ok_gradsfile & 17 20 & ,ok_limit,ok_etat0 21 logical hybrid ! vertcal coordinate is hybrid if true (sigma otherwise) 18 22 19 23 INTEGER iflag_phys,iflag_trac -
trunk/libf/dyn3d/sortvarc.F
r101 r124 63 63 64 64 c----------------------------------------------------------------------- 65 ! Ehouarn: when no initialization fields from file, resetvarc should be 66 ! set to false 67 if (firstcal) then 68 if (.not.read_start) then 69 resetvarc=.true. 70 endif 71 endif 65 72 66 73 dtvrs1j = dtvr/daysec
Note: See TracChangeset
for help on using the changeset viewer.