Changeset 127 for trunk/libf/dyn3d
- Timestamp:
- May 24, 2011, 1:26:29 PM (14 years ago)
- Location:
- trunk/libf/dyn3d
- Files:
-
- 10 edited
- 1 moved
Legend:
- Unmodified
- Added
- Removed
-
trunk/libf/dyn3d/comvert.h
r124 r127 1 1 ! 2 ! $Id: comvert.h 1 279 2009-12-10 09:02:56Z fairhead$2 ! $Id: comvert.h 1520 2011-05-23 11:37:09Z emillour $ 3 3 ! 4 4 !----------------------------------------------------------------------- 5 5 ! INCLUDE 'comvert.h' 6 6 7 COMMON/comvert /ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm),&7 COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm), & 8 8 & pa,preff,nivsigs(llm),nivsig(llm+1), & 9 9 & aps(llm),bps(llm),scaleheight 10 10 11 REAL ap,bp,presnivs,dpres,pa,preff,nivsigs,nivsig,aps,bps 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 12 24 real scaleheight ! atmospheric (reference) scale height (km) 13 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 14 32 !----------------------------------------------------------------------- -
trunk/libf/dyn3d/disvert.F90
r126 r127 1 ! $Id: disvert.F90 1 480 2011-01-31 21:29:58Z jghattas$1 ! $Id: disvert.F90 1520 2011-05-23 11:37:09Z emillour $ 2 2 3 SUBROUTINE disvert _terre(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, *)'disvert: 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,*)'disvert: 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,*) 'disvert: 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, *) 'disvert: BP '129 write(lunout, *) trim(modname),': BP ' 122 130 write(lunout, *) bp 123 write(lunout, *) 'disvert: 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, *) 'disvert: PRESNIVS '147 write(lunout, *) trim(modname),': PRESNIVS ' 140 148 write(lunout, *) presnivs 141 149 142 END SUBROUTINE disvert _terre150 END SUBROUTINE disvert -
trunk/libf/dyn3d/disvert_noterre.F
r124 r127 1 ! $Id: $ 1 2 SUBROUTINE disvert_noterre 2 3 … … 22 23 c 23 24 c======================================================================= 24 c Discretisation verticale en coordonnée hybride 25 c Discretisation verticale en coordonnée hybride (ou sigma) 25 26 c 26 27 c======================================================================= … … 49 50 integer iz 50 51 real z, ps,p 52 character(len=*),parameter :: modname="disvert_noterre" 51 53 52 54 c … … 54 56 c 55 57 ! Initializations: 56 pi=2.*ASIN(1.) 58 ! pi=2.*ASIN(1.) ! already done in iniconst 57 59 58 60 hybrid=.true. ! default value for hybrid (ie: use hybrid coordinates) 59 61 CALL getin('hybrid',hybrid) 60 write(lunout,*) 'disvert_noterre: hybrid=',hybrid62 write(lunout,*) trim(modname),': hybrid=',hybrid 61 63 62 64 ! Ouverture possible de fichiers typiquement E.T. … … 156 158 157 159 DO l=1,llm 158 nivsigs(l) = FLOAT(l)160 nivsigs(l) = REAL(l) 159 161 ENDDO 160 162 161 163 DO l=1,llmp1 162 nivsig(l)= FLOAT(l)164 nivsig(l)= REAL(l) 163 165 ENDDO 164 166 … … 199 201 bp(llmp1) = 0. 200 202 201 write(lunout,*) 'BP '203 write(lunout,*) trim(modname),': BP ' 202 204 write(lunout,*) bp 203 write(lunout,*) 'AP '205 write(lunout,*) trim(modname),': AP ' 204 206 write(lunout,*) ap 205 207 … … 225 227 end if 226 228 227 write(lunout,*) 'BPs '229 write(lunout,*) trim(modname),': BPs ' 228 230 write(lunout,*) bps 229 write(lunout,*) 'APs'231 write(lunout,*) trim(modname),': APs' 230 232 write(lunout,*) aps 231 233 … … 235 237 ENDDO 236 238 237 write(lunout,*) 'PRESNIVS'239 write(lunout,*)trim(modname),' : PRESNIVS' 238 240 write(lunout,*)presnivs 239 241 write(lunout,*)'Pseudo altitude of Presnivs : (for a scale ', -
trunk/libf/dyn3d/etat0_netcdf.F90
r66 r127 1 1 ! 2 ! $Id: etat0_netcdf.F90 1 486 2011-02-11 12:07:39Z fairhead$2 ! $Id: etat0_netcdf.F90 1520 2011-05-23 11:37:09Z emillour $ 3 3 ! 4 4 !------------------------------------------------------------------------------- 5 5 ! 6 SUBROUTINE etat0_netcdf(ib, masque, letat0)6 SUBROUTINE etat0_netcdf(ib, masque, phis, letat0) 7 7 ! 8 8 !------------------------------------------------------------------------------- … … 37 37 LOGICAL, INTENT(IN) :: ib ! barycentric interpolat. 38 38 REAL, DIMENSION(iip1,jjp1), INTENT(INOUT) :: masque ! land mask 39 REAL, DIMENSION(iip1,jjp1), INTENT(OUT) :: phis ! geopotentiel au sol 39 40 LOGICAL, INTENT(IN) :: letat0 ! F: masque only required 40 41 #ifndef CPP_EARTH … … 51 52 REAL, DIMENSION(klon) :: tsol, qsol 52 53 REAL, DIMENSION(klon) :: sn, rugmer, run_off_lic_0 53 REAL, DIMENSION(iip1,jjp1) :: orog, rugo, psol , phis54 REAL, DIMENSION(iip1,jjp1) :: orog, rugo, psol 54 55 REAL, DIMENSION(iip1,jjp1,llm+1) :: p3d 55 56 REAL, DIMENSION(iip1,jjp1,llm) :: uvent, t3d, tpot, qsat, qd … … 138 139 flag_aerosol, new_aod, & 139 140 bl95_b0, bl95_b1, & 140 iflag_thermals,nsplit_thermals,tau_thermals, & 141 iflag_thermals_ed,iflag_thermals_optflux, & 142 iflag_coupl,iflag_clos,iflag_wake, read_climoz, & 141 read_climoz, & 143 142 alp_offset) 144 143 … … 252 251 !******************************************************************************* 253 252 CALL pression(ip1jmp1, ap, bp, psol, p3d) 254 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 255 258 pls(:,:,:)=preff*(pk(:,:,:)/cpp)**(1./kappa) 256 259 ! WRITE(lunout,*) 'P3D :', p3d(10,20,:) -
trunk/libf/dyn3d/exner_hyb.F
r1 r127 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 -
trunk/libf/dyn3d/exner_milieu.F
r124 r127 48 48 REAL SSUM 49 49 EXTERNAL SSUM 50 logical,save :: firstcall=.true. 51 character(len=*),parameter :: modname="exner_milieu" 50 52 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) 53 ! Sanity check 54 if (firstcall) then 55 ! check that vertical discretization is compatible 56 ! with this routine 57 if (disvert_type.ne.2) then 58 call abort_gcm(modname, 59 & "this routine should only be called if disvert_type==2",42) 62 60 endif 63 61 62 ! sanity checks for Shallow Water case (1 vertical layer) 63 if (llm.eq.1) then 64 if (kappa.ne.1) then 65 call abort_gcm(modname, 66 & "kappa!=1 , but running in Shallow Water mode!!",42) 67 endif 68 if (cpp.ne.r) then 69 call abort_gcm(modname, 70 & "cpp!=r , but running in Shallow Water mode!!",42) 71 endif 72 endif ! of if (llm.eq.1) 73 74 firstcall=.false. 75 endif ! of if (firstcall) 76 77 !!!! Specific behaviour for Shallow Water (1 vertical layer) case: 78 if (llm.eq.1) then 79 64 80 ! Compute pks(:),pk(:),pkf(:) 65 81 … … 74 90 ! our work is done, exit routine 75 91 return 92 76 93 endif ! of if (llm.eq.1) 77 94 78 95 !!!! General case: 96 79 97 c ------------- 80 98 c Calcul de pks -
trunk/libf/dyn3d/guide_mod.F90
r1 r127 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 -
trunk/libf/dyn3d/iniacademic.F90
r124 r127 1 1 ! 2 ! $Id: iniacademic.F90 1 474 2011-01-14 11:04:45Z lguez$2 ! $Id: iniacademic.F90 1520 2011-05-23 11:37:09Z emillour $ 3 3 ! 4 4 SUBROUTINE iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0) … … 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 !----------------------------------------------------------------------- … … 76 79 ! -------------------------------------- 77 80 ! 78 79 write(lunout,*) 'Iniacademic'80 81 81 ! initialize planet radius, rotation rate,... 82 82 call conf_planete … … 136 136 teta0=315. ! mean Teta (S.H. 315K) 137 137 CALL getin('teta0',teta0) 138 write(lunout,*) 'Iniacademic - teta0 ',teta0139 write(lunout,*) 'Iniacademic - rad ',rad140 138 ttp=200. ! Tropopause temperature (S.H. 200K) 141 139 CALL getin('ttp',ttp) … … 183 181 tetajl(j,l)=teta0-delt_y*ddsin*ddsin+eps*ddsin & 184 182 -delt_z*(1.-ddsin*ddsin)*log(zsig) 185 !! Aymeric -- tests particuliers186 183 if (planet_type=="giant") then 187 184 tetajl(j,l)=teta0+(delt_y* & … … 207 204 enddo 208 205 enddo 209 ! write(lunout,*) 'Iniacademic - check',tetajl(:,int(llm/2)),rlatu(:)210 206 211 207 ! 3. Initialize fields (if necessary) … … 217 213 218 214 CALL pression ( ip1jmp1, ap, bp, ps, p ) 219 if (planet_type=="earth") then 220 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) 221 219 else 222 call exner_milieu(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf) 220 write(abort_message,*) "Wrong value for disvert_type: ", & 221 disvert_type 222 call abort_gcm(modname,abort_message,0) 223 223 endif 224 224 CALL massdair(p,masse) -
trunk/libf/dyn3d/iniconst.F
r109 r127 1 1 ! 2 ! $Id: iniconst.F 1 403 2010-07-01 09:02:53Z fairhead$2 ! $Id: iniconst.F 1520 2011-05-23 11:37:09Z emillour $ 3 3 ! 4 4 SUBROUTINE iniconst 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 … … 22 28 23 29 30 character(len=*),parameter :: modname="iniconst" 31 character(len=80) :: abort_message 24 32 c 25 33 c … … 49 57 r = cpp * kappa 50 58 51 write(lunout,*) 'iniconst: R CP Kappa ', r , cpp,kappa59 write(lunout,*) trim(modname),': R CP Kappa ',r,cpp,kappa 52 60 c 53 61 c----------------------------------------------------------------------- 54 62 55 if (planet_type.eq."earth") then 56 CALL disvert_terre(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig) 63 ! vertical discretization: default behavior depends on planet_type flag 64 if (planet_type=="earth") then 65 disvert_type=1 57 66 else 58 CALL disvert_noterre67 disvert_type=2 59 68 endif 60 c 61 RETURN 62 END 69 ! but user can also specify using one or the other in run.def: 70 call getin('disvert_type',disvert_type) 71 write(lunout,*) trim(modname),': disvert_type=',disvert_type 72 73 if (disvert_type==1) then 74 ! standard case for Earth (automatic generation of levels) 75 call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig, 76 & scaleheight) 77 else if (disvert_type==2) then 78 ! standard case for planets (levels generated using z2sig.def file) 79 call disvert_noterre 80 else 81 write(abort_message,*) "Wrong value for disvert_type: ", 82 & disvert_type 83 call abort_gcm(modname,abort_message,0) 84 endif 85 86 END -
trunk/libf/dyn3d/leapfrog.F
r119 r127 178 178 179 179 character*80 dynhist_file, dynhistave_file 180 character(len= 20) :: modname180 character(len=*),parameter :: modname="leapfrog" 181 181 character*80 abort_message 182 182 … … 206 206 endif 207 207 itaufinp1 = itaufin +1 208 modname="leapfrog"209 208 210 209 c INITIALISATIONS … … 238 237 dq(:,:,:)=0. 239 238 CALL pression ( ip1jmp1, ap, bp, ps, p ) 240 if ( planet_type.eq."earth") then239 if (disvert_type==1) then 241 240 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 242 else 241 else ! we assume that we are in the disvert_type==2 case 243 242 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 244 243 endif … … 409 408 410 409 CALL pression ( ip1jmp1, ap, bp, ps, p ) 411 if ( planet_type.eq."earth") then412 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )413 else 410 if (disvert_type==1) then 411 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta,pks, pk, pkf ) 412 else ! we assume that we are in the disvert_type==2 case 414 413 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 415 414 endif … … 531 530 532 531 CALL pression ( ip1jmp1, ap, bp, ps, p ) 533 if ( planet_type.eq."earth") then532 if (disvert_type==1) then 534 533 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 535 else 534 else ! we assume that we are in the disvert_type==2 case 536 535 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 537 536 endif -
trunk/libf/dyn3d/logic.h
r124 r127 1 1 ! 2 ! $Id: logic.h 1 319 2010-02-23 21:29:54Z fairhead$2 ! $Id: logic.h 1520 2011-05-23 11:37:09Z emillour $ 3 3 ! 4 4 ! … … 11 11 & statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus & 12 12 & ,read_start,ok_guide,ok_strato,ok_gradsfile & 13 & ,ok_limit,ok_etat0, hybrid13 & ,ok_limit,ok_etat0,grilles_gcm_netcdf,hybrid 14 14 15 15 COMMON/logici/ iflag_phys,iflag_trac … … 18 18 & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus & 19 19 & ,read_start,ok_guide,ok_strato,ok_gradsfile & 20 & ,ok_limit,ok_etat0 21 logical hybrid ! vertcal coordinate is hybrid if true (sigma otherwise) 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) 22 23 23 INTEGERiflag_phys,iflag_trac24 integer iflag_phys,iflag_trac 24 25 !-----------------------------------------------------------------------
Note: See TracChangeset
for help on using the changeset viewer.