Changeset 1520 for LMDZ5/trunk
- Timestamp:
- May 23, 2011, 1:37:09 PM (14 years ago)
- Location:
- LMDZ5/trunk/libf
- Files:
-
- 5 added
- 26 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/dyn3d/comvert.h
r1279 r1520 5 5 ! INCLUDE 'comvert.h' 6 6 7 COMMON/comvert/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm), & 8 & pa,preff,nivsigs(llm),nivsig(llm+1) 7 COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm), & 8 & pa,preff,nivsigs(llm),nivsig(llm+1), & 9 & aps(llm),bps(llm),scaleheight 9 10 10 REAL ap,bp,presnivs,dpres,pa,preff,nivsigs,nivsig 11 common/comverti/disvert_type 12 13 real ap ! hybrid pressure contribution at interlayers 14 real bp ! hybrid sigma contribution at interlayer 15 real presnivs ! (reference) pressure at mid-layers 16 real dpres 17 real pa ! reference pressure (Pa) at which hybrid coordinates 18 ! become purely pressure 19 real preff ! reference surface pressure (Pa) 20 real nivsigs 21 real nivsig 22 real aps ! hybrid pressure contribution at mid-layers 23 real bps ! hybrid sigma contribution at mid-layers 24 real scaleheight ! atmospheric (reference) scale height (km) 25 26 integer disvert_type ! type of vertical discretization: 27 ! 1: Earth (default for planet_type==earth), 28 ! automatic generation 29 ! 2: Planets (default for planet_type!=earth), 30 ! using 'z2sig.def' (or 'esasig.def) file 11 31 12 32 !----------------------------------------------------------------------- -
LMDZ5/trunk/libf/dyn3d/disvert.F90
r1492 r1520 1 1 ! $Id$ 2 2 3 SUBROUTINE disvert(pa, preff, ap, bp, dpres, presnivs, nivsigs, nivsig)3 SUBROUTINE disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,scaleheight) 4 4 5 5 ! Auteur : P. Le Van … … 17 17 ! ds(l) : distance entre les couches l et l-1 en coord.s 18 18 19 REAL pa, preff 20 REAL ap(llmp1), bp(llmp1), dpres(llm), nivsigs(llm), nivsig(llmp1) 21 REAL presnivs(llm) 19 real,intent(in) :: pa, preff 20 real,intent(out) :: ap(llmp1), bp(llmp1) 21 real,intent(out) :: dpres(llm), nivsigs(llm), nivsig(llmp1) 22 real,intent(out) :: presnivs(llm) 23 real,intent(out) :: scaleheight 22 24 23 25 REAL sig(llm+1), dsig(llm) … … 26 28 INTEGER l 27 29 REAL dsigmin 28 REAL alpha, beta, deltaz, h30 REAL alpha, beta, deltaz,scaleheight 29 31 INTEGER iostat 30 REAL pi, x 32 REAL x 33 character(len=*),parameter :: modname="disvert" 31 34 32 35 !----------------------------------------------------------------------- 33 36 34 pi = 2 * ASIN(1.) 37 ! default scaleheight is 8km for earth 38 scaleheight=8. 35 39 36 40 OPEN(99, file='sigma.def', status='old', form='formatted', iostat=iostat) … … 38 42 IF (iostat == 0) THEN 39 43 ! cas 1 on lit les options dans sigma.def: 40 READ(99, *) h! hauteur d'echelle 8.44 READ(99, *) scaleheight ! hauteur d'echelle 8. 41 45 READ(99, *) deltaz ! epaiseur de la premiere couche 0.04 42 46 READ(99, *) beta ! facteur d'acroissement en haut 1.3 … … 44 48 READ(99, *) k1 ! nombre de couches dans la transition haute 45 49 CLOSE(99) 46 alpha=deltaz/(llm*h) 47 write(lunout, *)'h, alpha, k0, k1, beta' 50 alpha=deltaz/(llm*scaleheight) 51 write(lunout, *)trim(modname),':scaleheight, alpha, k0, k1, beta', & 52 scaleheight, alpha, k0, k1, beta 48 53 49 54 alpha=deltaz/tanh(1./k0)*2. … … 51 56 sig(1)=1. 52 57 do l=1, llm 53 sig(l+1)=(cosh(l/k0))**(-alpha*k0/h) & 54 *exp(-alpha/h*tanh((llm-k1)/k0)*beta**(l-(llm-k1))/log(beta)) 55 zk=-h*log(sig(l+1)) 58 sig(l+1)=(cosh(l/k0))**(-alpha*k0/scaleheight) & 59 *exp(-alpha/scaleheight*tanh((llm-k1)/k0) & 60 *beta**(l-(llm-k1))/log(beta)) 61 zk=-scaleheight*log(sig(l+1)) 56 62 57 63 dzk1=alpha*tanh(l/k0) … … 73 79 dsigmin=1. 74 80 else 75 WRITE(LUNOUT,*) 'ATTENTION discretisation z a ajuster' 81 write(lunout,*) trim(modname), & 82 ' ATTENTION discretisation z a ajuster' 76 83 dsigmin=1. 77 84 endif 78 WRITE(LUNOUT,*) 'Discretisation verticale DSIGMIN=',dsigmin 85 write(lunout,*) trim(modname), & 86 ' Discretisation verticale DSIGMIN=',dsigmin 79 87 endif 80 88 … … 119 127 ap(llmp1) = pa * ( sig(llmp1) - bp(llmp1) ) 120 128 121 write(lunout, *) 'BP '129 write(lunout, *) trim(modname),': BP ' 122 130 write(lunout, *) bp 123 write(lunout, *) 'AP '131 write(lunout, *) trim(modname),': AP ' 124 132 write(lunout, *) ap 125 133 126 134 write(lunout, *) 'Niveaux de pressions approximatifs aux centres des' 127 135 write(lunout, *)'couches calcules pour une pression de surface =', preff 128 write(lunout, *) 'et altitudes equivalentes pour une hauteur d echelle de '129 write(lunout, *) '8km'136 write(lunout, *) 'et altitudes equivalentes pour une hauteur d echelle de ' 137 write(lunout, *) scaleheight,' km' 130 138 DO l = 1, llm 131 139 dpres(l) = bp(l) - bp(l+1) 132 140 presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff ) 133 141 write(lunout, *)'PRESNIVS(', l, ')=', presnivs(l), ' Z ~ ', & 134 log(preff/presnivs(l))* 8.&135 , ' DZ ~ ', 8.*log((ap(l)+bp(l)*preff)/ &142 log(preff/presnivs(l))*scaleheight & 143 , ' DZ ~ ', scaleheight*log((ap(l)+bp(l)*preff)/ & 136 144 max(ap(l+1)+bp(l+1)*preff, 1.e-10)) 137 145 ENDDO 138 146 139 write(lunout, *) 'PRESNIVS '147 write(lunout, *) trim(modname),': PRESNIVS ' 140 148 write(lunout, *) presnivs 141 149 -
LMDZ5/trunk/libf/dyn3d/etat0_netcdf.F90
r1511 r1520 251 251 !******************************************************************************* 252 252 CALL pression(ip1jmp1, ap, bp, psol, p3d) 253 CALL exner_hyb(ip1jmp1, psol, p3d, alpha, beta, pks, pk, y) 253 if (disvert_type.eq.1) then 254 CALL exner_hyb(ip1jmp1, psol, p3d, alpha, beta, pks, pk, y) 255 else ! we assume that we are in the disvert_type==2 case 256 CALL exner_milieu(ip1jmp1,psol,p3d,beta,pks,pk,y) 257 endif 254 258 pls(:,:,:)=preff*(pk(:,:,:)/cpp)**(1./kappa) 255 259 ! WRITE(lunout,*) 'P3D :', p3d(10,20,:) -
LMDZ5/trunk/libf/dyn3d/exner_hyb.F
r1403 r1520 51 51 REAL SSUM 52 52 c 53 logical,save :: firstcall=.true. 54 character(len=*),parameter :: modname="exner_hyb" 55 56 ! Sanity check 57 if (firstcall) then 58 ! check that vertical discretization is compatible 59 ! with this routine 60 if (disvert_type.ne.1) then 61 call abort_gcm(modname, 62 & "this routine should only be called if disvert_type==1",42) 63 endif 64 65 ! sanity checks for Shallow Water case (1 vertical layer) 66 if (llm.eq.1) then 67 if (kappa.ne.1) then 68 call abort_gcm(modname, 69 & "kappa!=1 , but running in Shallow Water mode!!",42) 70 endif 71 if (cpp.ne.r) then 72 call abort_gcm(modname, 73 & "cpp!=r , but running in Shallow Water mode!!",42) 74 endif 75 endif ! of if (llm.eq.1) 76 77 firstcall=.false. 78 endif ! of if (firstcall) 53 79 54 80 if (llm.eq.1) then 55 ! Specific behaviour for Shallow Water (1 vertical layer) case56 57 ! Sanity checks58 if (kappa.ne.1) then59 call abort_gcm("exner_hyb",60 & "kappa!=1 , but running in Shallow Water mode!!",42)61 endif62 if (cpp.ne.r) then63 call abort_gcm("exner_hyb",64 & "cpp!=r , but running in Shallow Water mode!!",42)65 endif66 81 67 82 ! Compute pks(:),pk(:),pkf(:) … … 77 92 ! our work is done, exit routine 78 93 return 94 79 95 endif ! of if (llm.eq.1) 80 96 97 !!!! General case: 81 98 82 99 unpl2k = 1.+ 2.* kappa -
LMDZ5/trunk/libf/dyn3d/guide_mod.F90
r1403 r1520 644 644 ! ----------------------------------------------------------------- 645 645 CALL pression( ip1jmp1, ap, bp, psi, p ) 646 CALL exner_hyb(ip1jmp1,psi,p,alpha,beta,pks,pk,pkf) 647 646 if (disvert_type==1) then 647 CALL exner_hyb(ip1jmp1,psi,p,alpha,beta,pks,pk,pkf) 648 else ! we assume that we are in the disvert_type==2 case 649 CALL exner_milieu(ip1jmp1,psi,p,beta,pks,pk,pkf) 650 endif 648 651 ! .... Calcul de pls , pression au milieu des couches ,en Pascals 649 652 unskap=1./kappa -
LMDZ5/trunk/libf/dyn3d/iniacademic.F90
r1505 r1520 71 71 72 72 REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm),zdtvr 73 74 character(len=*),parameter :: modname="iniacademic" 75 character(len=80) :: abort_message 73 76 74 77 !----------------------------------------------------------------------- … … 210 213 211 214 CALL pression ( ip1jmp1, ap, bp, ps, p ) 212 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 215 if (disvert_type.eq.1) then 216 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 217 elseif (disvert_type.eq.2) then 218 call exner_milieu(ip1jmp1,ps,p,beta,pks,pk,pkf) 219 else 220 write(abort_message,*) "Wrong value for disvert_type: ", & 221 disvert_type 222 call abort_gcm(modname,abort_message,0) 223 endif 213 224 CALL massdair(p,masse) 214 225 -
LMDZ5/trunk/libf/dyn3d/iniconst.F
r1502 r1520 5 5 6 6 USE control_mod 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 7 13 8 14 IMPLICIT NONE … … 21 27 #include "iniprint.h" 22 28 23 29 character(len=*),parameter :: modname="iniconst" 30 character(len=80) :: abort_message 24 31 c 25 32 c … … 48 55 r = cpp * kappa 49 56 50 write(lunout,*) 'iniconst: R CP Kappa ', r , cpp,kappa57 write(lunout,*) trim(modname),': R CP Kappa ',r,cpp,kappa 51 58 c 52 59 c----------------------------------------------------------------------- 53 60 54 CALL disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig) 55 c 56 c 57 RETURN 58 END 61 ! vertical discretization: default behavior depends on planet_type flag 62 if (planet_type=="earth") then 63 disvert_type=1 64 else 65 disvert_type=2 66 endif 67 ! but user can also specify using one or the other in run.def: 68 call getin('disvert_type',disvert_type) 69 write(lunout,*) trim(modname),': disvert_type=',disvert_type 70 71 if (disvert_type==1) then 72 ! standard case for Earth (automatic generation of levels) 73 call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig, 74 & scaleheight) 75 else if (disvert_type==2) then 76 ! standard case for planets (levels generated using z2sig.def file) 77 call disvert_noterre 78 else 79 write(abort_message,*) "Wrong value for disvert_type: ", 80 & disvert_type 81 call abort_gcm(modname,abort_message,0) 82 endif 83 84 END -
LMDZ5/trunk/libf/dyn3d/leapfrog.F
r1505 r1520 172 172 173 173 character*80 dynhist_file, dynhistave_file 174 character(len= 20) :: modname174 character(len=*),parameter :: modname="leapfrog" 175 175 character*80 abort_message 176 176 … … 193 193 itaufin = nday*day_step 194 194 itaufinp1 = itaufin +1 195 modname="leapfrog"196 195 197 196 … … 211 210 dq(:,:,:)=0. 212 211 CALL pression ( ip1jmp1, ap, bp, ps, p ) 213 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 212 if (disvert_type==1) then 213 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 214 else ! we assume that we are in the disvert_type==2 case 215 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 216 endif 214 217 215 218 c----------------------------------------------------------------------- … … 359 362 360 363 CALL pression ( ip1jmp1, ap, bp, ps, p ) 361 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta,pks, pk, pkf ) 364 if (disvert_type==1) then 365 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta,pks, pk, pkf ) 366 else ! we assume that we are in the disvert_type==2 case 367 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 368 endif 362 369 363 370 ! rdaym_ini = itau * dtvr / daysec … … 463 470 464 471 CALL pression ( ip1jmp1, ap, bp, ps, p ) 465 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 472 if (disvert_type==1) then 473 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 474 else ! we assume that we are in the disvert_type==2 case 475 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 476 endif 466 477 467 478 -
LMDZ5/trunk/libf/dyn3d/limy.F
r524 r1520 1 ! 2 ! $Header$3 ! 1 c 2 c $Id$ 3 c 4 4 SUBROUTINE limy(s0,sy,sm,pente_max) 5 5 c … … 40 40 REAL qbyv(ip1jm,llm) 41 41 42 REAL qpns,qpsn,ap n,aps,dyn1,dys1,dyn2,dys242 REAL qpns,qpsn,appn,apps,dyn1,dys1,dyn2,dys2 43 43 Logical extremum,first 44 44 save first … … 117 117 118 118 c print*,dyqv(iip1+1) 119 c ap n=abs(dyq(1)/dyqv(iip1+1))119 c appn=abs(dyq(1)/dyqv(iip1+1)) 120 120 c print*,dyq(ip1jm+1) 121 121 c print*,dyqv(ip1jm-iip1+1) 122 c ap s=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1))122 c apps=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1)) 123 123 c do ij=2,iim 124 c ap n=amax1(abs(dyq(ij)/dyqv(ij)),apn)125 c ap s=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),aps)124 c appn=amax1(abs(dyq(ij)/dyqv(ij)),appn) 125 c apps=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),apps) 126 126 c enddo 127 c ap n=min(pente_max/apn,1.)128 c ap s=min(pente_max/aps,1.)127 c appn=min(pente_max/appn,1.) 128 c apps=min(pente_max/apps,1.) 129 129 130 130 … … 132 132 133 133 c if(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.) 134 c & ap n=0.134 c & appn=0. 135 135 c if(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)* 136 136 c & dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.) 137 c & ap s=0.137 c & apps=0. 138 138 139 139 c limitation des pentes aux poles 140 140 c do ij=1,iip1 141 c dyq(ij)=ap n*dyq(ij)142 c dyq(ip1jm+ij)=ap s*dyq(ip1jm+ij)141 c dyq(ij)=appn*dyq(ij) 142 c dyq(ip1jm+ij)=apps*dyq(ip1jm+ij) 143 143 c enddo 144 144 -
LMDZ5/trunk/libf/dyn3d/logic.h
r1492 r1520 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,grilles_gcm_netcdf 13 & ,ok_limit,ok_etat0,grilles_gcm_netcdf,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,grilles_gcm_netcdf 21 logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise) 22 ! (only used if disvert_type==2) 18 23 19 INTEGER iflag_phys24 integer iflag_phys,iflag_trac 20 25 !----------------------------------------------------------------------- -
LMDZ5/trunk/libf/dyn3d/vlsplt.F
r595 r1520 1 ! 2 ! $Header$ 3 ! 4 c 1 c 2 c $Id$ 5 3 c 6 4 … … 478 476 REAL qbyv(ip1jm,llm) 479 477 480 REAL qpns,qpsn,ap n,aps,dyn1,dys1,dyn2,dys2,newmasse,fn,fs478 REAL qpns,qpsn,appn,apps,dyn1,dys1,dyn2,dys2,newmasse,fn,fs 481 479 c REAL newq,oldmasse 482 480 Logical extremum,first,testcpu … … 602 600 C PRINT*,dyq(1) 603 601 C PRINT*,dyqv(iip1+1) 604 C ap n=abs(dyq(1)/dyqv(iip1+1))602 C appn=abs(dyq(1)/dyqv(iip1+1)) 605 603 C PRINT*,dyq(ip1jm+1) 606 604 C PRINT*,dyqv(ip1jm-iip1+1) 607 C ap s=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1))605 C apps=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1)) 608 606 C DO ij=2,iim 609 C ap n=amax1(abs(dyq(ij)/dyqv(ij)),apn)610 C ap s=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),aps)607 C appn=amax1(abs(dyq(ij)/dyqv(ij)),appn) 608 C apps=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),apps) 611 609 C ENDDO 612 C ap n=min(pente_max/apn,1.)613 C ap s=min(pente_max/aps,1.)610 C appn=min(pente_max/appn,1.) 611 C apps=min(pente_max/apps,1.) 614 612 C 615 613 C … … 617 615 C 618 616 C IF(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.) 619 C & ap n=0.617 C & appn=0. 620 618 C IF(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)* 621 619 C & dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.) 622 C & ap s=0.620 C & apps=0. 623 621 C 624 622 C limitation des pentes aux poles 625 623 C DO ij=1,iip1 626 C dyq(ij)=ap n*dyq(ij)627 C dyq(ip1jm+ij)=ap s*dyq(ip1jm+ij)624 C dyq(ij)=appn*dyq(ij) 625 C dyq(ip1jm+ij)=apps*dyq(ip1jm+ij) 628 626 C ENDDO 629 627 C -
LMDZ5/trunk/libf/dyn3d/vlspltqs.F
r595 r1520 1 ! 2 ! $Header$3 ! 1 c 2 c $Id$ 3 c 4 4 SUBROUTINE vlspltqs ( q,pente_max,masse,w,pbaru,pbarv,pdt, 5 5 , p,pk,teta ) … … 634 634 C PRINT*,dyq(1) 635 635 C PRINT*,dyqv(iip1+1) 636 C ap n=abs(dyq(1)/dyqv(iip1+1))636 C appn=abs(dyq(1)/dyqv(iip1+1)) 637 637 C PRINT*,dyq(ip1jm+1) 638 638 C PRINT*,dyqv(ip1jm-iip1+1) 639 C ap s=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1))639 C apps=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1)) 640 640 C DO ij=2,iim 641 C ap n=amax1(abs(dyq(ij)/dyqv(ij)),apn)642 C ap s=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),aps)641 C appn=amax1(abs(dyq(ij)/dyqv(ij)),appn) 642 C apps=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),apps) 643 643 C ENDDO 644 C ap n=min(pente_max/apn,1.)645 C ap s=min(pente_max/aps,1.)644 C appn=min(pente_max/appn,1.) 645 C apps=min(pente_max/apps,1.) 646 646 C 647 647 C … … 649 649 C 650 650 C IF(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.) 651 C & ap n=0.651 C & appn=0. 652 652 C IF(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)* 653 653 C & dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.) 654 C & ap s=0.654 C & apps=0. 655 655 C 656 656 C limitation des pentes aux poles 657 657 C DO ij=1,iip1 658 C dyq(ij)=ap n*dyq(ij)659 C dyq(ip1jm+ij)=ap s*dyq(ip1jm+ij)658 C dyq(ij)=appn*dyq(ij) 659 C dyq(ip1jm+ij)=apps*dyq(ip1jm+ij) 660 660 C ENDDO 661 661 C -
LMDZ5/trunk/libf/dyn3dpar/comvert.h
r1279 r1520 1 1 ! 2 ! $ Header$2 ! $Id$ 3 3 ! 4 4 !----------------------------------------------------------------------- 5 5 ! INCLUDE 'comvert.h' 6 6 7 COMMON/comvert/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm), & 8 & pa,preff,nivsigs(llm),nivsig(llm+1) 7 COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm), & 8 & pa,preff,nivsigs(llm),nivsig(llm+1), & 9 & aps(llm),bps(llm),scaleheight 9 10 10 REAL ap,bp,presnivs,dpres,pa,preff,nivsigs,nivsig11 common/comverti/disvert_type 11 12 12 !----------------------------------------------------------------------- 13 real ap ! hybrid pressure contribution at interlayers 14 real bp ! hybrid sigma contribution at interlayer 15 real presnivs ! (reference) pressure at mid-layers 16 real dpres 17 real pa ! reference pressure (Pa) at which hybrid coordinates 18 ! become purely pressure 19 real preff ! reference surface pressure (Pa) 20 real nivsigs 21 real nivsig 22 real aps ! hybrid pressure contribution at mid-layers 23 real bps ! hybrid sigma contribution at mid-layers 24 real scaleheight ! atmospheric (reference) scale height (km) 25 26 integer disvert_type ! type of vertical discretization: 27 ! 1: Earth (default for planet_type==earth), 28 ! automatic generation 29 ! 2: Planets (default for planet_type!=earth), 30 ! using 'z2sig.def' (or 'esasig.def) file 31 32 !----------------------------------------------------------------------- -
LMDZ5/trunk/libf/dyn3dpar/disvert.F90
r1492 r1520 1 1 ! $Id$ 2 2 3 SUBROUTINE disvert(pa, preff, ap, bp, dpres, presnivs, nivsigs, nivsig)3 SUBROUTINE disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,scaleheight) 4 4 5 5 ! Auteur : P. Le Van … … 17 17 ! ds(l) : distance entre les couches l et l-1 en coord.s 18 18 19 REAL pa, preff 20 REAL ap(llmp1), bp(llmp1), dpres(llm), nivsigs(llm), nivsig(llmp1) 21 REAL presnivs(llm) 19 real,intent(in) :: pa, preff 20 real,intent(out) :: ap(llmp1), bp(llmp1) 21 real,intent(out) :: dpres(llm), nivsigs(llm), nivsig(llmp1) 22 real,intent(out) :: presnivs(llm) 23 real,intent(out) :: scaleheight 22 24 23 25 REAL sig(llm+1), dsig(llm) … … 26 28 INTEGER l 27 29 REAL dsigmin 28 REAL alpha, beta, deltaz, h30 REAL alpha, beta, deltaz,scaleheight 29 31 INTEGER iostat 30 REAL pi, x 32 REAL x 33 character(len=*),parameter :: modname="disvert" 31 34 32 35 !----------------------------------------------------------------------- 33 36 34 pi = 2 * ASIN(1.) 37 ! default scaleheight is 8km for earth 38 scaleheight=8. 35 39 36 40 OPEN(99, file='sigma.def', status='old', form='formatted', iostat=iostat) … … 38 42 IF (iostat == 0) THEN 39 43 ! cas 1 on lit les options dans sigma.def: 40 READ(99, *) h! hauteur d'echelle 8.44 READ(99, *) scaleheight ! hauteur d'echelle 8. 41 45 READ(99, *) deltaz ! epaiseur de la premiere couche 0.04 42 46 READ(99, *) beta ! facteur d'acroissement en haut 1.3 … … 44 48 READ(99, *) k1 ! nombre de couches dans la transition haute 45 49 CLOSE(99) 46 alpha=deltaz/(llm*h) 47 write(lunout, *)'h, alpha, k0, k1, beta' 50 alpha=deltaz/(llm*scaleheight) 51 write(lunout, *)trim(modname),':scaleheight, alpha, k0, k1, beta', & 52 scaleheight, alpha, k0, k1, beta 48 53 49 54 alpha=deltaz/tanh(1./k0)*2. … … 51 56 sig(1)=1. 52 57 do l=1, llm 53 sig(l+1)=(cosh(l/k0))**(-alpha*k0/h) & 54 *exp(-alpha/h*tanh((llm-k1)/k0)*beta**(l-(llm-k1))/log(beta)) 55 zk=-h*log(sig(l+1)) 58 sig(l+1)=(cosh(l/k0))**(-alpha*k0/scaleheight) & 59 *exp(-alpha/scaleheight*tanh((llm-k1)/k0) & 60 *beta**(l-(llm-k1))/log(beta)) 61 zk=-scaleheight*log(sig(l+1)) 56 62 57 63 dzk1=alpha*tanh(l/k0) … … 73 79 dsigmin=1. 74 80 else 75 WRITE(LUNOUT,*) 'ATTENTION discretisation z a ajuster' 81 write(lunout,*) trim(modname), & 82 ' ATTENTION discretisation z a ajuster' 76 83 dsigmin=1. 77 84 endif 78 WRITE(LUNOUT,*) 'Discretisation verticale DSIGMIN=',dsigmin 85 write(lunout,*) trim(modname), & 86 ' Discretisation verticale DSIGMIN=',dsigmin 79 87 endif 80 88 … … 119 127 ap(llmp1) = pa * ( sig(llmp1) - bp(llmp1) ) 120 128 121 write(lunout, *) 'BP '129 write(lunout, *) trim(modname),': BP ' 122 130 write(lunout, *) bp 123 write(lunout, *) 'AP '131 write(lunout, *) trim(modname),': AP ' 124 132 write(lunout, *) ap 125 133 126 134 write(lunout, *) 'Niveaux de pressions approximatifs aux centres des' 127 135 write(lunout, *)'couches calcules pour une pression de surface =', preff 128 write(lunout, *) 'et altitudes equivalentes pour une hauteur d echelle de '129 write(lunout, *) '8km'136 write(lunout, *) 'et altitudes equivalentes pour une hauteur d echelle de ' 137 write(lunout, *) scaleheight,' km' 130 138 DO l = 1, llm 131 139 dpres(l) = bp(l) - bp(l+1) 132 140 presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff ) 133 141 write(lunout, *)'PRESNIVS(', l, ')=', presnivs(l), ' Z ~ ', & 134 log(preff/presnivs(l))* 8.&135 , ' DZ ~ ', 8.*log((ap(l)+bp(l)*preff)/ &142 log(preff/presnivs(l))*scaleheight & 143 , ' DZ ~ ', scaleheight*log((ap(l)+bp(l)*preff)/ & 136 144 max(ap(l+1)+bp(l+1)*preff, 1.e-10)) 137 145 ENDDO 138 146 139 write(lunout, *) 'PRESNIVS '147 write(lunout, *) trim(modname),': PRESNIVS ' 140 148 write(lunout, *) presnivs 141 149 -
LMDZ5/trunk/libf/dyn3dpar/etat0_netcdf.F90
r1511 r1520 251 251 !******************************************************************************* 252 252 CALL pression(ip1jmp1, ap, bp, psol, p3d) 253 CALL exner_hyb(ip1jmp1, psol, p3d, alpha, beta, pks, pk, y) 253 if (disvert_type.eq.1) then 254 CALL exner_hyb(ip1jmp1, psol, p3d, alpha, beta, pks, pk, y) 255 else ! we assume that we are in the disvert_type==2 case 256 CALL exner_milieu(ip1jmp1,psol,p3d,beta,pks,pk,y) 257 endif 254 258 pls(:,:,:)=preff*(pk(:,:,:)/cpp)**(1./kappa) 255 259 ! WRITE(lunout,*) 'P3D :', p3d(10,20,:) -
LMDZ5/trunk/libf/dyn3dpar/exner_hyb.F
r1403 r1520 51 51 REAL SSUM 52 52 c 53 logical,save :: firstcall=.true. 54 character(len=*),parameter :: modname="exner_hyb" 55 56 ! Sanity check 57 if (firstcall) then 58 ! check that vertical discretization is compatible 59 ! with this routine 60 if (disvert_type.ne.1) then 61 call abort_gcm(modname, 62 & "this routine should only be called if disvert_type==1",42) 63 endif 64 65 ! sanity checks for Shallow Water case (1 vertical layer) 66 if (llm.eq.1) then 67 if (kappa.ne.1) then 68 call abort_gcm(modname, 69 & "kappa!=1 , but running in Shallow Water mode!!",42) 70 endif 71 if (cpp.ne.r) then 72 call abort_gcm(modname, 73 & "cpp!=r , but running in Shallow Water mode!!",42) 74 endif 75 endif ! of if (llm.eq.1) 76 77 firstcall=.false. 78 endif ! of if (firstcall) 53 79 54 80 if (llm.eq.1) then 55 ! Specific behaviour for Shallow Water (1 vertical layer) case56 57 ! Sanity checks58 if (kappa.ne.1) then59 call abort_gcm("exner_hyb",60 & "kappa!=1 , but running in Shallow Water mode!!",42)61 endif62 if (cpp.ne.r) then63 call abort_gcm("exner_hyb",64 & "cpp!=r , but running in Shallow Water mode!!",42)65 endif66 81 67 82 ! Compute pks(:),pk(:),pkf(:) … … 77 92 ! our work is done, exit routine 78 93 return 94 79 95 endif ! of if (llm.eq.1) 80 96 97 !!!! General case: 81 98 82 99 unpl2k = 1.+ 2.* kappa -
LMDZ5/trunk/libf/dyn3dpar/exner_hyb_p.F
r1403 r1520 53 53 EXTERNAL SSUM 54 54 INTEGER ije,ijb,jje,jjb 55 c 56 c$OMP BARRIER 57 58 if (llm.eq.1) then 59 ! Specific behaviour for Shallow Water (1 vertical layer) case 60 61 ! Sanity checks 62 if (kappa.ne.1) then 63 call abort_gcm("exner_hyb", 64 & "kappa!=1 , but running in Shallow Water mode!!",42) 65 endif 66 if (cpp.ne.r) then 67 call abort_gcm("exner_hyb", 68 & "cpp!=r , but running in Shallow Water mode!!",42) 55 logical,save :: firstcall=.true. 56 !$OMP THREADPRIVATE(firstcall) 57 character(len=*),parameter :: modname="exner_hyb_p" 58 c 59 60 ! Sanity check 61 if (firstcall) then 62 ! check that vertical discretization is compatible 63 ! with this routine 64 if (disvert_type.ne.1) then 65 call abort_gcm(modname, 66 & "this routine should only be called if disvert_type==1",42) 69 67 endif 70 68 69 ! sanity checks for Shallow Water case (1 vertical layer) 70 if (llm.eq.1) then 71 if (kappa.ne.1) then 72 call abort_gcm(modname, 73 & "kappa!=1 , but running in Shallow Water mode!!",42) 74 endif 75 if (cpp.ne.r) then 76 call abort_gcm(modname, 77 & "cpp!=r , but running in Shallow Water mode!!",42) 78 endif 79 endif ! of if (llm.eq.1) 80 81 firstcall=.false. 82 endif ! of if (firstcall) 83 84 c$OMP BARRIER 85 86 ! Specific behaviour for Shallow Water (1 vertical layer) case 87 if (llm.eq.1) then 88 71 89 ! Compute pks(:),pk(:),pkf(:) 72 90 ijb=ij_begin … … 116 134 endif ! of if (llm.eq.1) 117 135 136 !!!! General case: 118 137 119 138 unpl2k = 1.+ 2.* kappa -
LMDZ5/trunk/libf/dyn3dpar/gcm.F
r1454 r1520 538 538 c write(78,*) 'q',q 539 539 540 c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logic /)540 c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/) 541 541 CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,clesphy0, 542 542 . time_0) -
LMDZ5/trunk/libf/dyn3dpar/guide_p_mod.F90
r1512 r1520 455 455 ! Calcul niveaux pression milieu de couches 456 456 CALL pression_p( ip1jmp1, ap, bp, ps, p ) 457 CALL exner_hyb_p(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf) 458 unskap=1./kappa 457 if (disvert_type==1) then 458 CALL exner_hyb_p(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf) 459 else 460 CALL exner_milieu_p(ip1jmp1,ps,p,beta,pks,pk,pkf) 461 endif 462 unskap=1./kappa 459 463 DO l = 1, llm 460 464 DO j=jjb_u,jje_u … … 751 755 ELSE 752 756 CALL pression_p( ip1jmp1, ap, bp, psi, p ) 753 CALL exner_hyb_p(ip1jmp1,psi,p,alpha,beta,pks,pk,pkf) 757 if (disvert_type==1) then 758 CALL exner_hyb_p(ip1jmp1,psi,p,alpha,beta,pks,pk,pkf) 759 else ! we assume that we are in the disvert_type==2 case 760 CALL exner_milieu_p(ip1jmp1,psi,p,beta,pks,pk,pkf) 761 endif 754 762 unskap=1./kappa 755 763 DO l = 1, llm -
LMDZ5/trunk/libf/dyn3dpar/iniacademic.F90
r1505 r1520 71 71 72 72 REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm),zdtvr 73 74 character(len=*),parameter :: modname="iniacademic" 75 character(len=80) :: abort_message 73 76 74 77 !----------------------------------------------------------------------- … … 210 213 211 214 CALL pression ( ip1jmp1, ap, bp, ps, p ) 212 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 215 if (disvert_type.eq.1) then 216 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 217 elseif (disvert_type.eq.2) then 218 call exner_milieu(ip1jmp1,ps,p,beta,pks,pk,pkf) 219 else 220 write(abort_message,*) "Wrong value for disvert_type: ", & 221 disvert_type 222 call abort_gcm(modname,abort_message,0) 223 endif 213 224 CALL massdair(p,masse) 214 225 -
LMDZ5/trunk/libf/dyn3dpar/iniconst.F
r1502 r1520 5 5 6 6 USE control_mod 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 7 13 8 14 IMPLICIT NONE … … 21 27 #include "iniprint.h" 22 28 23 29 character(len=*),parameter :: modname="iniconst" 30 character(len=80) :: abort_message 24 31 c 25 32 c … … 48 55 r = cpp * kappa 49 56 50 write(lunout,*) 'iniconst: R CP Kappa ', r , cpp,kappa57 write(lunout,*) trim(modname),': R CP Kappa ',r,cpp,kappa 51 58 c 52 59 c----------------------------------------------------------------------- 53 60 54 CALL disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig) 55 c 56 c 57 RETURN 58 END 61 ! vertical discretization: default behavior depends on planet_type flag 62 if (planet_type=="earth") then 63 disvert_type=1 64 else 65 disvert_type=2 66 endif 67 ! but user can also specify using one or the other in run.def: 68 call getin('disvert_type',disvert_type) 69 write(lunout,*) trim(modname),': disvert_type=',disvert_type 70 71 if (disvert_type==1) then 72 ! standard case for Earth (automatic generation of levels) 73 call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig, 74 & scaleheight) 75 else if (disvert_type==2) then 76 ! standard case for planets (levels generated using z2sig.def file) 77 call disvert_noterre 78 else 79 write(abort_message,*) "Wrong value for disvert_type: ", 80 & disvert_type 81 call abort_gcm(modname,abort_message,0) 82 endif 83 84 END -
LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F
r1505 r1520 164 164 165 165 character*80 dynhist_file, dynhistave_file 166 character *20 modname166 character(len=*),parameter :: modname="leapfrog" 167 167 character*80 abort_message 168 168 … … 208 208 itaufin = nday*day_step 209 209 itaufinp1 = itaufin +1 210 modname="leapfrog_p"211 210 212 211 itau = 0 … … 236 235 dq(:,:,:)=0. 237 236 CALL pression ( ip1jmp1, ap, bp, ps, p ) 238 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 237 if (disvert_type==1) then 238 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 239 else ! we assume that we are in the disvert_type==2 case 240 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 241 endif 239 242 c$OMP END MASTER 240 243 c----------------------------------------------------------------------- … … 691 694 692 695 c$OMP BARRIER 693 CALL exner_hyb_p( ip1jmp1, ps, p,alpha,beta,pks, pk, pkf ) 696 if (disvert_type==1) then 697 CALL exner_hyb_p( ip1jmp1, ps, p,alpha,beta,pks, pk, pkf ) 698 else ! we assume that we are in the disvert_type==2 case 699 CALL exner_milieu_p( ip1jmp1, ps, p, beta, pks, pk, pkf ) 700 endif 694 701 c$OMP BARRIER 695 702 jD_cur = jD_ref + day_ini - day_ref … … 1030 1037 CALL pression_p ( ip1jmp1, ap, bp, ps, p ) 1031 1038 c$OMP BARRIER 1032 CALL exner_hyb_p( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 1039 if (disvert_type==1) then 1040 CALL exner_hyb_p( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 1041 else ! we assume that we are in the disvert_type==2 case 1042 CALL exner_milieu_p( ip1jmp1, ps, p, beta, pks, pk, pkf ) 1043 endif 1033 1044 c$OMP BARRIER 1034 1045 -
LMDZ5/trunk/libf/dyn3dpar/limy.F
r764 r1520 1 ! 2 ! $Header$3 ! 1 c 2 c $Id$ 3 c 4 4 SUBROUTINE limy(s0,sy,sm,pente_max) 5 5 c … … 40 40 REAL qbyv(ip1jm,llm) 41 41 42 REAL qpns,qpsn,ap n,aps,dyn1,dys1,dyn2,dys242 REAL qpns,qpsn,appn,apps,dyn1,dys1,dyn2,dys2 43 43 Logical extremum,first 44 44 save first … … 52 52 REAL SSUM 53 53 integer ismax,ismin 54 EXTERNAL SSUM, ismin,ismax 54 EXTERNAL SSUM, convflu,ismin,ismax 55 EXTERNAL filtreg 55 56 56 57 data first/.true./ … … 116 117 117 118 c print*,dyqv(iip1+1) 118 c ap n=abs(dyq(1)/dyqv(iip1+1))119 c appn=abs(dyq(1)/dyqv(iip1+1)) 119 120 c print*,dyq(ip1jm+1) 120 121 c print*,dyqv(ip1jm-iip1+1) 121 c ap s=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1))122 c apps=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1)) 122 123 c do ij=2,iim 123 c ap n=amax1(abs(dyq(ij)/dyqv(ij)),apn)124 c ap s=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),aps)124 c appn=amax1(abs(dyq(ij)/dyqv(ij)),appn) 125 c apps=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),apps) 125 126 c enddo 126 c ap n=min(pente_max/apn,1.)127 c ap s=min(pente_max/aps,1.)127 c appn=min(pente_max/appn,1.) 128 c apps=min(pente_max/apps,1.) 128 129 129 130 … … 131 132 132 133 c if(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.) 133 c & ap n=0.134 c & appn=0. 134 135 c if(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)* 135 136 c & dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.) 136 c & ap s=0.137 c & apps=0. 137 138 138 139 c limitation des pentes aux poles 139 140 c do ij=1,iip1 140 c dyq(ij)=ap n*dyq(ij)141 c dyq(ip1jm+ij)=ap s*dyq(ip1jm+ij)141 c dyq(ij)=appn*dyq(ij) 142 c dyq(ip1jm+ij)=apps*dyq(ip1jm+ij) 142 143 c enddo 143 144 -
LMDZ5/trunk/libf/dyn3dpar/logic.h
r1492 r1520 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,grilles_gcm_netcdf 13 & ,ok_limit,ok_etat0,grilles_gcm_netcdf,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,grilles_gcm_netcdf 21 logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise) 22 ! (only used if disvert_type==2) 18 23 19 INTEGER iflag_phys 20 !$OMP THREADPRIVATE(/logic/) 24 integer iflag_phys,iflag_trac 25 !$OMP THREADPRIVATE(/logicl/) 26 !$OMP THREADPRIVATE(/logici/) 21 27 !----------------------------------------------------------------------- -
LMDZ5/trunk/libf/dyn3dpar/vlsplt_p.F
r764 r1520 1 c 2 c $Id$ 3 c 4 1 5 SUBROUTINE vlsplt_p(q,pente_max,masse,w,pbaru,pbarv,pdt) 2 6 c … … 561 565 REAL qbyv(ip1jm,llm) 562 566 563 REAL qpns,qpsn,ap n,aps,dyn1,dys1,dyn2,dys2,newmasse,fn,fs567 REAL qpns,qpsn,appn,apps,dyn1,dys1,dyn2,dys2,newmasse,fn,fs 564 568 c REAL newq,oldmasse 565 569 Logical extremum,first,testcpu … … 732 736 C PRINT*,dyq(1) 733 737 C PRINT*,dyqv(iip1+1) 734 C ap n=abs(dyq(1)/dyqv(iip1+1))738 C appn=abs(dyq(1)/dyqv(iip1+1)) 735 739 C PRINT*,dyq(ip1jm+1) 736 740 C PRINT*,dyqv(ip1jm-iip1+1) 737 C ap s=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1))741 C apps=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1)) 738 742 C DO ij=2,iim 739 C ap n=amax1(abs(dyq(ij)/dyqv(ij)),apn)740 C ap s=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),aps)743 C appn=amax1(abs(dyq(ij)/dyqv(ij)),appn) 744 C apps=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),apps) 741 745 C ENDDO 742 C ap n=min(pente_max/apn,1.)743 C ap s=min(pente_max/aps,1.)746 C appn=min(pente_max/appn,1.) 747 C apps=min(pente_max/apps,1.) 744 748 C 745 749 C … … 747 751 C 748 752 C IF(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.) 749 C & ap n=0.753 C & appn=0. 750 754 C IF(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)* 751 755 C & dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.) 752 C & ap s=0.756 C & apps=0. 753 757 C 754 758 C limitation des pentes aux poles 755 759 C DO ij=1,iip1 756 C dyq(ij)=ap n*dyq(ij)757 C dyq(ip1jm+ij)=ap s*dyq(ip1jm+ij)760 C dyq(ij)=appn*dyq(ij) 761 C dyq(ip1jm+ij)=apps*dyq(ip1jm+ij) 758 762 C ENDDO 759 763 C -
LMDZ5/trunk/libf/dyn3dpar/vlspltqs_p.F
r764 r1520 1 ! 2 ! $Header$3 ! 1 c 2 c $Id$ 3 c 4 4 SUBROUTINE vlspltqs_p ( q,pente_max,masse,w,pbaru,pbarv,pdt, 5 5 , p,pk,teta ) … … 772 772 C PRINT*,dyq(1) 773 773 C PRINT*,dyqv(iip1+1) 774 C ap n=abs(dyq(1)/dyqv(iip1+1))774 C appn=abs(dyq(1)/dyqv(iip1+1)) 775 775 C PRINT*,dyq(ip1jm+1) 776 776 C PRINT*,dyqv(ip1jm-iip1+1) 777 C ap s=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1))777 C apps=abs(dyq(ip1jm+1)/dyqv(ip1jm-iip1+1)) 778 778 C DO ij=2,iim 779 C ap n=amax1(abs(dyq(ij)/dyqv(ij)),apn)780 C ap s=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),aps)779 C appn=amax1(abs(dyq(ij)/dyqv(ij)),appn) 780 C apps=amax1(abs(dyq(ip1jm+ij)/dyqv(ip1jm-iip1+ij)),apps) 781 781 C ENDDO 782 C ap n=min(pente_max/apn,1.)783 C ap s=min(pente_max/aps,1.)782 C appn=min(pente_max/appn,1.) 783 C apps=min(pente_max/apps,1.) 784 784 C 785 785 C … … 787 787 C 788 788 C IF(dyqv(ismin(iim,dyqv,1))*dyqv(ismax(iim,dyqv,1)).le.0.) 789 C & ap n=0.789 C & appn=0. 790 790 C IF(dyqv(ismax(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1)* 791 791 C & dyqv(ismin(iim,dyqv(ip1jm-iip1+1),1)+ip1jm-iip1+1).le.0.) 792 C & ap s=0.792 C & apps=0. 793 793 C 794 794 C limitation des pentes aux poles 795 795 C DO ij=1,iip1 796 C dyq(ij)=ap n*dyq(ij)797 C dyq(ip1jm+ij)=ap s*dyq(ip1jm+ij)796 C dyq(ij)=appn*dyq(ij) 797 C dyq(ip1jm+ij)=apps*dyq(ip1jm+ij) 798 798 C ENDDO 799 799 C
Note: See TracChangeset
for help on using the changeset viewer.