Changeset 1665 for LMDZ5/branches/testing/libf
- Timestamp:
- Oct 9, 2012, 3:35:26 PM (12 years ago)
- Location:
- LMDZ5/branches/testing
- Files:
-
- 6 deleted
- 81 edited
- 42 copied
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/branches/testing
- Property svn:mergeinfo changed
/LMDZ5/trunk merged: 1576-1580,1582,1584,1591-1593,1597-1598,1600,1604-1620,1622-1628
- Property svn:mergeinfo changed
-
LMDZ5/branches/testing/libf/dyn3d/calfis.F
r1407 r1665 165 165 PARAMETER(ntetaSTD=3) 166 166 REAL rtetaSTD(ntetaSTD) 167 DATA rtetaSTD/350., 380., 405./ 167 DATA rtetaSTD/350., 380., 405./ ! Earth-specific values, beware !! 168 168 REAL PVteta(ngridmx,ntetaSTD) 169 169 c … … 434 434 c 435 435 if (planet_type=="earth") then 436 #ifdef CPP_EARTH 436 #ifdef CPP_PHYS 437 ! PVtheta calls tetalevel, which is in the physics 437 438 cIM calcul PV a teta=350, 380, 405K 438 439 CALL PVtheta(ngridmx,llm,pucov,pvcov,pteta, … … 450 451 451 452 452 if (planet_type=="earth") then453 #ifdef CPP_EARTH454 453 455 454 ! write(lunout,*) 'PHYSIQUE AVEC NSPLIT_PHYS=',nsplit_phys … … 460 459 zdqfic(:,:,:)=0. 461 460 462 do isplit=1,nsplit_phys 461 if (planet_type=="earth") then 462 #ifdef CPP_PHYS 463 464 do isplit=1,nsplit_phys 463 465 464 466 jH_cur_split=jH_cur+(isplit-1) * dtvr / (daysec *nsplit_phys) … … 503 505 zdqfic(:,:,:)=zdqfic(:,:,:)+zdqfi(:,:,:) 504 506 505 enddo 507 enddo ! of do isplit=1,nsplit_phys 508 509 #endif 510 ! of #ifdef CPP_PHYS 511 endif ! of if (planet_type=="earth") 512 506 513 zdufi(:,:)=zdufic(:,:)/nsplit_phys 507 514 zdvfi(:,:)=zdvfic(:,:)/nsplit_phys … … 509 516 zdqfi(:,:,:)=zdqfic(:,:,:)/nsplit_phys 510 517 511 #endif512 endif !of if (planet_type=="earth")513 518 514 519 500 CONTINUE -
LMDZ5/branches/testing/libf/dyn3d/ce0l.F90
r1664 r1665 28 28 IMPLICIT NONE 29 29 #ifndef CPP_EARTH 30 #include "iniprint.h" 30 31 WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics' 31 32 #else -
LMDZ5/branches/testing/libf/dyn3d/comvert.h
r1520 r1665 9 9 & aps(llm),bps(llm),scaleheight 10 10 11 common/comverti/disvert_type 11 common/comverti/disvert_type, pressure_exner 12 12 13 13 real ap ! hybrid pressure contribution at interlayers … … 30 30 ! using 'z2sig.def' (or 'esasig.def) file 31 31 32 logical pressure_exner 33 ! compute pressure inside layers using Exner function, else use mean 34 ! of pressure values at interfaces 35 32 36 !----------------------------------------------------------------------- -
LMDZ5/branches/testing/libf/dyn3d/conf_gcm.F
r1664 r1665 155 155 nday = 10 156 156 CALL getin('nday',nday) 157 158 !Config Key = starttime 159 !Config Desc = Heure de depart de la simulation 160 !Config Def = 0 161 !Config Help = Heure de depart de la simulation 162 !Config en jour 163 starttime = 0 164 CALL getin('starttime',starttime) 157 165 158 166 !Config Key = day_step -
LMDZ5/branches/testing/libf/dyn3d/control_mod.F90
r1502 r1665 10 10 IMPLICIT NONE 11 11 12 REAL :: periodav 12 REAL :: periodav, starttime 13 13 INTEGER :: nday,day_step,iperiod,iapp_tracvl,nsplit_phys 14 14 INTEGER :: iconser,iecri,dissip_period,iphysiq,iecrimoy -
LMDZ5/branches/testing/libf/dyn3d/disvert.F90
r1524 r1665 4 4 5 5 ! Auteur : P. Le Van 6 7 use new_unit_m, only: new_unit 8 use ioipsl, only: getin 6 9 7 10 IMPLICIT NONE … … 26 29 real zk, zkm1, dzk1, dzk2, k0, k1 27 30 28 INTEGER l 31 INTEGER l, unit 29 32 REAL dsigmin 30 33 REAL alpha, beta, deltaz 31 INTEGER iostat32 34 REAL x 33 35 character(len=*),parameter :: modname="disvert" 34 36 37 character(len=6):: vert_sampling 38 ! (allowed values are "param", "tropo", "strato" and "read") 39 35 40 !----------------------------------------------------------------------- 41 42 print *, "Call sequence information: disvert" 36 43 37 44 ! default scaleheight is 8km for earth 38 45 scaleheight=8. 39 46 40 OPEN(99, file='sigma.def', status='old', form='formatted', iostat=iostat) 47 vert_sampling = merge("strato", "tropo ", ok_strato) ! default value 48 call getin('vert_sampling', vert_sampling) 49 print *, 'vert_sampling = ' // vert_sampling 41 50 42 IF (iostat == 0) THEN 43 ! cas 1 on lit les options dans sigma.def: 51 select case (vert_sampling) 52 case ("param") 53 ! On lit les options dans sigma.def: 54 OPEN(99, file='sigma.def', status='old', form='formatted') 44 55 READ(99, *) scaleheight ! hauteur d'echelle 8. 45 56 READ(99, *) deltaz ! epaiseur de la premiere couche 0.04 … … 68 79 69 80 sig(llm+1)=0. 70 71 DO l = 1, llm 72 dsig(l) = sig(l)-sig(l+1) 73 end DO 74 ELSE 75 if (ok_strato) then 76 if (llm==39) then 77 dsigmin=0.3 78 else if (llm==50) then 79 dsigmin=1. 80 else 81 write(lunout,*) trim(modname), & 82 ' ATTENTION discretisation z a ajuster' 83 dsigmin=1. 84 endif 85 write(lunout,*) trim(modname), & 86 ' Discretisation verticale DSIGMIN=',dsigmin 87 endif 88 81 case("tropo") 89 82 DO l = 1, llm 90 83 x = 2*asin(1.) * (l - 0.5) / (llm + 1) 91 92 IF (ok_strato) THEN 93 dsig(l) =(dsigmin + 7. * SIN(x)**2) & 94 *(0.5*(1.-tanh(1.*(x-asin(1.))/asin(1.))))**2 95 ELSE 96 dsig(l) = 1.0 + 7.0 * SIN(x)**2 97 ENDIF 84 dsig(l) = 1.0 + 7.0 * SIN(x)**2 98 85 ENDDO 99 86 dsig = dsig / sum(dsig) … … 102 89 sig(l) = sig(l+1) + dsig(l) 103 90 ENDDO 104 ENDIF 91 case("strato") 92 if (llm==39) then 93 dsigmin=0.3 94 else if (llm==50) then 95 dsigmin=1. 96 else 97 write(lunout,*) trim(modname), ' ATTENTION discretisation z a ajuster' 98 dsigmin=1. 99 endif 100 WRITE(LUNOUT,*) trim(modname), 'Discretisation verticale DSIGMIN=',dsigmin 101 102 DO l = 1, llm 103 x = 2*asin(1.) * (l - 0.5) / (llm + 1) 104 dsig(l) =(dsigmin + 7. * SIN(x)**2) & 105 *(0.5*(1.-tanh(1.*(x-asin(1.))/asin(1.))))**2 106 ENDDO 107 dsig = dsig / sum(dsig) 108 sig(llm+1) = 0. 109 DO l = llm, 1, -1 110 sig(l) = sig(l+1) + dsig(l) 111 ENDDO 112 case("read") 113 call new_unit(unit) 114 open(unit, file="hybrid.txt", status="old", action="read", & 115 position="rewind") 116 read(unit, fmt=*) ! skip title line 117 do l = 1, llm + 1 118 read(unit, fmt=*) sig(l) 119 end do 120 close(unit) 121 case default 122 call abort_gcm("disvert", 'Wrong value for "vert_sampling"', 1) 123 END select 105 124 106 125 DO l=1, llm -
LMDZ5/branches/testing/libf/dyn3d/dynetat0.F
r1421 r1665 119 119 day_ini = tab_cntrl(30) 120 120 itau_dyn = tab_cntrl(31) 121 start_time = tab_cntrl(32) 121 122 c ................................................................. 122 123 c -
LMDZ5/branches/testing/libf/dyn3d/dynredem.F
r1664 r1665 120 120 tab_cntrl(30) = REAL(iday_end) 121 121 tab_cntrl(31) = REAL(itau_dyn + itaufin) 122 c start_time: start_time of simulation (not necessarily 0.) 123 tab_cntrl(32) = start_time 122 124 c 123 125 c ......................................................... -
LMDZ5/branches/testing/libf/dyn3d/etat0_netcdf.F90
r1520 r1665 251 251 !******************************************************************************* 252 252 CALL pression(ip1jmp1, ap, bp, psol, p3d) 253 if ( disvert_type.eq.1) then253 if (pressure_exner) then 254 254 CALL exner_hyb(ip1jmp1, psol, p3d, alpha, beta, pks, pk, y) 255 else ! we assume that we are in the disvert_type==2 case255 else 256 256 CALL exner_milieu(ip1jmp1,psol,p3d,beta,pks,pk,y) 257 257 endif -
LMDZ5/branches/testing/libf/dyn3d/exner_hyb.F
r1520 r1665 56 56 ! Sanity check 57 57 if (firstcall) then 58 ! check that vertical discretization is compatible59 ! with this routine60 if (disvert_type.ne.1) then61 call abort_gcm(modname,62 & "this routine should only be called if disvert_type==1",42)63 endif64 65 58 ! sanity checks for Shallow Water case (1 vertical layer) 66 59 if (llm.eq.1) then -
LMDZ5/branches/testing/libf/dyn3d/exner_milieu.F
r1520 r1665 53 53 ! Sanity check 54 54 if (firstcall) then 55 ! check that vertical discretization is compatible56 ! with this routine57 if (disvert_type.ne.2) then58 call abort_gcm(modname,59 & "this routine should only be called if disvert_type==2",42)60 endif61 62 55 ! sanity checks for Shallow Water case (1 vertical layer) 63 56 if (llm.eq.1) then -
LMDZ5/branches/testing/libf/dyn3d/gcm.F
r1664 r1665 21 21 ! A nettoyer. On ne veut qu'une ou deux routines d'interface 22 22 ! dynamique -> physique pour l'initialisation 23 ! Ehouarn: for now these only apply to Earth: 24 #ifdef CPP_EARTH 23 #ifdef CPP_PHYS 25 24 USE dimphy 26 25 USE comgeomphy … … 88 87 89 88 REAL zdtvr 90 INTEGER nbetatmoy, nbetatdem,nbetat91 89 92 90 c variables dynamiques … … 181 179 ! A nettoyer. On ne veut qu'une ou deux routines d'interface 182 180 ! dynamique -> physique pour l'initialisation 183 ! Ehouarn : temporarily (?) keep this only for Earth 184 if (planet_type.eq."earth") then 185 #ifdef CPP_EARTH 181 #ifdef CPP_PHYS 186 182 CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/)) 187 183 call InitComgeomphy 188 184 #endif 189 endif190 185 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 191 186 c----------------------------------------------------------------------- … … 305 300 C on remet le calendrier à zero si demande 306 301 c 302 IF (start_time /= starttime) then 303 WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le' 304 &,' fichier restart ne correspond pas à celle lue dans le run.def' 305 IF (raz_date == 1) then 306 WRITE(lunout,*)'Je prends l''heure lue dans run.def' 307 start_time = starttime 308 ELSE 309 WRITE(lunout,*)'Je m''arrete' 310 CALL abort 311 ENDIF 312 ENDIF 307 313 IF (raz_date == 1) THEN 308 314 annee_ref = anneeref … … 373 379 #endif 374 380 375 c nombre d'etats dans les fichiers demarrage et histoire376 nbetatdem = nday / iecri377 nbetatmoy = nday / periodav + 1378 381 379 382 if (iflag_phys.eq.1) then … … 428 431 WRITE(lunout,*) 429 432 . 'GCM: WARNING!!! vitesse verticale nulle dans la physique' 430 ! Earth: 431 if (planet_type.eq."earth") then 432 #ifdef CPP_EARTH 433 ! Physics: 434 #ifdef CPP_PHYS 433 435 CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys , 434 436 , latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp ) 435 437 #endif 436 endif ! of if (planet_type.eq."earth")437 438 call_iniphys=.false. 438 439 ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1)) 439 !#endif440 440 441 441 c numero de stockage pour les fichiers de redemarrage: … … 459 459 #endif 460 460 461 #ifdef CPP_ EARTH461 #ifdef CPP_PHYS 462 462 ! Create start file (startphy.nc) and boundary conditions (limit.nc) 463 463 ! for the Earth verstion -
LMDZ5/branches/testing/libf/dyn3d/guide_mod.F90
r1520 r1665 644 644 ! ----------------------------------------------------------------- 645 645 CALL pression( ip1jmp1, ap, bp, psi, p ) 646 if ( disvert_type==1) then646 if (pressure_exner) then 647 647 CALL exner_hyb(ip1jmp1,psi,p,alpha,beta,pks,pk,pkf) 648 else ! we assume that we are in the disvert_type==2 case648 else 649 649 CALL exner_milieu(ip1jmp1,psi,p,beta,pks,pk,pkf) 650 650 endif -
LMDZ5/branches/testing/libf/dyn3d/iniacademic.F90
r1664 r1665 222 222 223 223 CALL pression ( ip1jmp1, ap, bp, ps, p ) 224 if ( disvert_type.eq.1) then224 if (pressure_exner) then 225 225 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 226 else if (disvert_type.eq.2) then226 else 227 227 call exner_milieu(ip1jmp1,ps,p,beta,pks,pk,pkf) 228 else229 write(abort_message,*) "Wrong value for disvert_type: ", &230 disvert_type231 call abort_gcm(modname,abort_message,0)232 228 endif 233 229 CALL massdair(p,masse) -
LMDZ5/branches/testing/libf/dyn3d/inidissip.F90
r1502 r1665 28 28 ! Local variables: 29 29 REAL fact,zvert(llm),zz 30 REAL zh(ip1jmp1),zu(ip1jmp1),zv(ip1jm),deltap(ip1jmp1,llm) 30 REAL zh(ip1jmp1),zu(ip1jmp1), gx(ip1jmp1), divgra(ip1jmp1) 31 real zv(ip1jm), gy(ip1jm), deltap(ip1jmp1,llm) 31 32 REAL ullm,vllm,umin,vmin,zhmin,zhmax 32 REAL zllm ,z1llm33 REAL zllm 33 34 34 35 INTEGER l,ij,idum,ii … … 78 79 DO l = 1,50 79 80 IF(lstardis) THEN 80 CALL divgrad2(1,zh,deltap,niterh, zh)81 CALL divgrad2(1,zh,deltap,niterh,divgra) 81 82 ELSE 82 CALL divgrad (1,zh,niterh, zh)83 CALL divgrad (1,zh,niterh,divgra) 83 84 ENDIF 84 85 85 CALL minmax(iip1*jjp1,zh,zhmin,zhmax ) 86 87 zllm = ABS( zhmax ) 88 z1llm = 1./zllm 89 DO ij = 1,ip1jmp1 90 zh(ij) = zh(ij)* z1llm 91 ENDDO 86 zllm = ABS(maxval(divgra)) 87 zh = divgra / zllm 92 88 ENDDO 93 89 … … 123 119 !cccc CALL covcont( 1,zu,zv,zu,zv ) 124 120 IF(lstardis) THEN 125 CALL gradiv2( 1,zu,zv,nitergdiv, zu,zv)121 CALL gradiv2( 1,zu,zv,nitergdiv,gx,gy ) 126 122 ELSE 127 CALL gradiv ( 1,zu,zv,nitergdiv, zu,zv)123 CALL gradiv ( 1,zu,zv,nitergdiv,gx,gy ) 128 124 ENDIF 129 125 ELSE 130 126 IF(lstardis) THEN 131 CALL nxgraro2( 1,zu,zv,nitergrot, zu,zv)127 CALL nxgraro2( 1,zu,zv,nitergrot,gx,gy ) 132 128 ELSE 133 CALL nxgrarot( 1,zu,zv,nitergrot, zu,zv)129 CALL nxgrarot( 1,zu,zv,nitergrot,gx,gy ) 134 130 ENDIF 135 131 ENDIF 136 132 137 CALL minmax(iip1*jjp1,zu,umin,ullm ) 138 CALL minmax(iip1*jjm, zv,vmin,vllm ) 139 140 ullm = ABS ( ullm ) 141 vllm = ABS ( vllm ) 142 143 zllm = MAX( ullm,vllm ) 144 z1llm = 1./ zllm 145 DO ij = 1, ip1jmp1 146 zu(ij) = zu(ij)* z1llm 147 ENDDO 148 DO ij = 1, ip1jm 149 zv(ij) = zv(ij)* z1llm 150 ENDDO 133 zllm = max(abs(maxval(gx)), abs(maxval(gy))) 134 zu = gx / zllm 135 zv = gy / zllm 151 136 end DO 152 137 -
LMDZ5/branches/testing/libf/dyn3d/inigrads.F
r524 r1665 9 9 implicit none 10 10 11 integer if,im,jm,lm,i,j,l ,lnblnk11 integer if,im,jm,lm,i,j,l 12 12 real x(im),y(jm),z(lm),fx,fy,fz,dt 13 13 real xmin,xmax,ymin,ymax … … 40 40 ivar(if)=0 41 41 42 fichier(if)= file(1:lnblnk(file))42 fichier(if)=trim(file) 43 43 44 44 firsttime(if)=.true. … … 70 70 71 71 print*,4*(ifd(if)-iid(if))*(jfd(if)-jid(if)) 72 print*, file(1:lnblnk(file))//'.dat'72 print*,trim(file)//'.dat' 73 73 74 OPEN (unit(if)+1,FILE= file(1:lnblnk(file))//'.dat'74 OPEN (unit(if)+1,FILE=trim(file)//'.dat' 75 75 s ,FORM='unformatted', 76 76 s ACCESS='direct' -
LMDZ5/branches/testing/libf/dyn3d/integrd.F
r1550 r1665 4 4 SUBROUTINE integrd 5 5 $ ( nq,vcovm1,ucovm1,tetam1,psm1,massem1, 6 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis,finvmaold ) 6 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis !,finvmaold 7 & ) 7 8 8 9 use control_mod, only : planet_type … … 34 35 #include "temps.h" 35 36 #include "serre.h" 37 #include "iniprint.h" 36 38 37 39 c Arguments: 38 40 c ---------- 39 41 40 INTEGER nq 41 42 REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm) 43 REAL q(ip1jmp1,llm,nq) 44 REAL ps(ip1jmp1),masse(ip1jmp1,llm),phis(ip1jmp1) 45 46 REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm) 47 REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1),massem1(ip1jmp1,llm) 48 49 REAL dv(ip1jm,llm),du(ip1jmp1,llm) 50 REAL dteta(ip1jmp1,llm),dp(ip1jmp1) 51 REAL dq(ip1jmp1,llm,nq), finvmaold(ip1jmp1,llm) 42 integer,intent(in) :: nq ! number of tracers to handle in this routine 43 real,intent(inout) :: vcov(ip1jm,llm) ! covariant meridional wind 44 real,intent(inout) :: ucov(ip1jmp1,llm) ! covariant zonal wind 45 real,intent(inout) :: teta(ip1jmp1,llm) ! potential temperature 46 real,intent(inout) :: q(ip1jmp1,llm,nq) ! advected tracers 47 real,intent(inout) :: ps(ip1jmp1) ! surface pressure 48 real,intent(inout) :: masse(ip1jmp1,llm) ! atmospheric mass 49 real,intent(in) :: phis(ip1jmp1) ! ground geopotential !!! unused 50 ! values at previous time step 51 real,intent(inout) :: vcovm1(ip1jm,llm) 52 real,intent(inout) :: ucovm1(ip1jmp1,llm) 53 real,intent(inout) :: tetam1(ip1jmp1,llm) 54 real,intent(inout) :: psm1(ip1jmp1) 55 real,intent(inout) :: massem1(ip1jmp1,llm) 56 ! the tendencies to add 57 real,intent(in) :: dv(ip1jm,llm) 58 real,intent(in) :: du(ip1jmp1,llm) 59 real,intent(in) :: dteta(ip1jmp1,llm) 60 real,intent(in) :: dp(ip1jmp1) 61 real,intent(in) :: dq(ip1jmp1,llm,nq) !!! unused 62 ! real,intent(out) :: finvmaold(ip1jmp1,llm) !!! unused 52 63 53 64 c Local: … … 55 66 56 67 REAL vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1) 57 REAL massescr( ip1jmp1,llm ), finvmasse(ip1jmp1,llm) 68 REAL massescr( ip1jmp1,llm ) 69 ! REAL finvmasse(ip1jmp1,llm) 58 70 REAL p(ip1jmp1,llmp1) 59 71 REAL tpn,tps,tppn(iim),tpps(iim) … … 61 73 REAL deltap( ip1jmp1,llm ) 62 74 63 INTEGER l,ij,iq 75 INTEGER l,ij,iq,i,j 64 76 65 77 REAL SSUM … … 88 100 DO ij = 1,ip1jmp1 89 101 IF( ps(ij).LT.0. ) THEN 90 PRINT*,' Au point ij = ',ij, ' , pression sol neg. ', ps(ij) 91 print *, ' dans integrd' 92 stop 1 102 write(lunout,*) "integrd: negative surface pressure ",ps(ij) 103 write(lunout,*) " at node ij =", ij 104 ! since ij=j+(i-1)*jjp1 , we have 105 j=modulo(ij,jjp1) 106 i=1+(ij-j)/jjp1 107 write(lunout,*) " lon = ",rlonv(i)*180./pi, " deg", 108 & " lat = ",rlatu(j)*180./pi, " deg" 109 stop 93 110 ENDIF 94 111 ENDDO … … 110 127 CALL massdair ( p , masse ) 111 128 112 CALL SCOPY( ijp1llm , masse, 1, finvmasse, 1 ) 113 CALL filtreg( finvmasse, jjp1, llm, -2, 2, .TRUE., 1 ) 129 ! Ehouarn : we don't use/need finvmaold and finvmasse, 130 ! so might as well not compute them 131 ! CALL SCOPY( ijp1llm , masse, 1, finvmasse, 1 ) 132 ! CALL filtreg( finvmasse, jjp1, llm, -2, 2, .TRUE., 1 ) 114 133 c 115 134 … … 218 237 ENDDO 219 238 220 221 CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 )239 ! Ehouarn: forget about finvmaold 240 ! CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 ) 222 241 223 242 endif ! of if (planet_type.eq."earth") -
LMDZ5/branches/testing/libf/dyn3d/leapfrog.F
r1529 r1665 72 72 73 73 real zqmin,zqmax 74 INTEGER nbetatmoy, nbetatdem,nbetat75 74 76 75 c variables dynamiques … … 118 117 119 118 REAL SSUM 120 REAL time_0 , finvmaold(ip1jmp1,llm) 119 REAL time_0 120 ! REAL finvmaold(ip1jmp1,llm) 121 121 122 122 cym LOGICAL lafin … … 212 212 dq(:,:,:)=0. 213 213 CALL pression ( ip1jmp1, ap, bp, ps, p ) 214 if ( disvert_type==1) then214 if (pressure_exner) then 215 215 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 216 else ! we assume that we are in the disvert_type==2 case216 else 217 217 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 218 218 endif … … 222 222 c ---------------------------------- 223 223 224 1 CONTINUE 225 226 jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec) 227 jH_cur = jH_ref + & 228 & (itau * dtvr / daysec - int(itau * dtvr / daysec)) 224 1 CONTINUE ! Matsuno Forward step begins here 225 226 jD_cur = jD_ref + day_ini - day_ref + & 227 & itau/day_step 228 jH_cur = jH_ref + start_time + & 229 & mod(itau,day_step)/float(day_step) 230 jD_cur = jD_cur + int(jH_cur) 231 jH_cur = jH_cur - int(jH_cur) 229 232 230 233 … … 255 258 256 259 c ... P.Le Van .26/04/94 .... 257 258 CALL SCOPY ( ijp1llm, masse, 1, finvmaold, 1 )259 CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )260 261 2 CONTINUE 260 ! Ehouarn: finvmaold is actually not used 261 ! CALL SCOPY ( ijp1llm, masse, 1, finvmaold, 1 ) 262 ! CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 ) 263 264 2 CONTINUE ! Matsuno backward or leapfrog step begins here 262 265 263 266 c----------------------------------------------------------------------- … … 302 305 c -------------------------------- 303 306 307 ! compute geopotential phi() 304 308 CALL geopot ( ip1jmp1, teta , pk , pks, phis , phi ) 305 309 … … 315 319 316 320 IF( forward. OR . leapf ) THEN 317 321 ! Ehouarn: NB: at this point p with ps are not synchronized 322 ! (whereas mass and ps are...) 318 323 CALL caladvtrac(q,pbaru,pbarv, 319 324 * p, masse, dq, teta, … … 340 345 341 346 CALL integrd ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 , 342 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,343 $ finvmaold )347 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ) 348 ! $ finvmaold ) 344 349 345 350 … … 364 369 365 370 CALL pression ( ip1jmp1, ap, bp, ps, p ) 366 if ( disvert_type==1) then371 if (pressure_exner) then 367 372 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta,pks, pk, pkf ) 368 else ! we assume that we are in the disvert_type==2 case373 else 369 374 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 370 375 endif … … 372 377 ! rdaym_ini = itau * dtvr / daysec 373 378 ! rdayvrai = rdaym_ini + day_ini 374 jD_cur = jD_ref + day_ini - day_ref 375 $ + int (itau * dtvr / daysec) 376 jH_cur = jH_ref + & 377 & (itau * dtvr / daysec - int(itau * dtvr / daysec)) 379 ! jD_cur = jD_ref + day_ini - day_ref 380 ! $ + int (itau * dtvr / daysec) 381 ! jH_cur = jH_ref + & 382 ! & (itau * dtvr / daysec - int(itau * dtvr / daysec)) 383 jD_cur = jD_ref + day_ini - day_ref + & 384 & itau/day_step 385 jH_cur = jH_ref + start_time + & 386 & mod(itau,day_step)/float(day_step) 387 jD_cur = jD_cur + int(jH_cur) 388 jH_cur = jH_cur - int(jH_cur) 378 389 ! write(lunout,*)'itau, jD_cur = ', itau, jD_cur, jH_cur 379 390 ! call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes) … … 394 405 ! Ehouarn: be careful, diagedyn is Earth-specific (includes ../phylmd/..)! 395 406 IF (planet_type.eq."earth") THEN 407 #ifdef CPP_EARTH 396 408 CALL diagedyn(ztit,2,1,1,dtphys 397 409 & , ucov , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2)) 410 #endif 398 411 ENDIF 399 412 ENDIF ! of IF (ip_ebil_dyn.ge.1 ) … … 472 485 473 486 CALL pression ( ip1jmp1, ap, bp, ps, p ) 474 if ( disvert_type==1) then487 if (pressure_exner) then 475 488 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 476 else ! we assume that we are in the disvert_type==2 case489 else 477 490 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 478 491 endif … … 529 542 ENDDO 530 543 531 DO ij = 1,iim 532 tppn(ij) = aire( ij ) * ps ( ij ) 533 tpps(ij) = aire(ij+ip1jm) * ps (ij+ip1jm) 534 ENDDO 535 tpn = SSUM(iim,tppn,1)/apoln 536 tps = SSUM(iim,tpps,1)/apols 537 538 DO ij = 1, iip1 539 ps( ij ) = tpn 540 ps(ij+ip1jm) = tps 541 ENDDO 542 544 if (1 == 0) then 545 !!! Ehouarn: lines here 1) kill 1+1=2 in the dynamics 546 !!! 2) should probably not be here anyway 547 !!! but are kept for those who would want to revert to previous behaviour 548 DO ij = 1,iim 549 tppn(ij) = aire( ij ) * ps ( ij ) 550 tpps(ij) = aire(ij+ip1jm) * ps (ij+ip1jm) 551 ENDDO 552 tpn = SSUM(iim,tppn,1)/apoln 553 tps = SSUM(iim,tpps,1)/apols 554 555 DO ij = 1, iip1 556 ps( ij ) = tpn 557 ps(ij+ip1jm) = tps 558 ENDDO 559 endif ! of if (1 == 0) 543 560 544 561 END IF ! of IF(apdiss) … … 622 639 ! Ehouarn: output only during LF or Backward Matsuno 623 640 if (leapf.or.(.not.leapf.and.(.not.forward))) then 624 nbetat = nbetatdem625 641 CALL geopot(ip1jmp1,teta,pk,pks,phis,phi) 626 642 unat=0. … … 652 668 ! if (planet_type.eq."earth") then 653 669 ! Write an Earth-format restart file 654 CALL dynredem1("restart.nc", 0.0,670 CALL dynredem1("restart.nc",start_time, 655 671 & vcov,ucov,teta,q,masse,ps) 656 672 ! endif ! of if (planet_type.eq."earth") 657 673 658 674 CLOSE(99) 675 !!! Ehouarn: Why not stop here and now? 659 676 ENDIF ! of IF (itau.EQ.itaufin) 660 677 … … 740 757 IF(MOD(itau,iecri ).EQ.0) THEN 741 758 c IF(MOD(itau,iecri*day_step).EQ.0) THEN 742 nbetat = nbetatdem743 759 CALL geopot(ip1jmp1,teta,pk,pks,phis,phi) 744 760 unat=0. … … 763 779 IF(itau.EQ.itaufin) THEN 764 780 ! if (planet_type.eq."earth") then 765 CALL dynredem1("restart.nc", 0.0,781 CALL dynredem1("restart.nc",start_time, 766 782 & vcov,ucov,teta,q,masse,ps) 767 783 ! endif ! of if (planet_type.eq."earth") -
LMDZ5/branches/testing/libf/dyn3d/temps.h
r1279 r1665 14 14 15 15 COMMON/temps/itaufin, dt, day_ini, day_end, annee_ref, day_ref, & 16 & itau_dyn, itau_phy, jD_ref, jH_ref, calend 16 & itau_dyn, itau_phy, jD_ref, jH_ref, calend, & 17 & start_time 18 17 19 18 20 INTEGER itaufin 19 21 INTEGER itau_dyn, itau_phy 20 22 INTEGER day_ini, day_end, annee_ref, day_ref 21 REAL dt, jD_ref, jH_ref 23 REAL dt, jD_ref, jH_ref, start_time 22 24 CHARACTER (len=10) :: calend 23 25 -
LMDZ5/branches/testing/libf/dyn3d/wrgrads.F
r1025 r1665 26 26 c local 27 27 28 integer im,jm,lm,i,j,l, lnblnk,iv,iii,iji,iif,ijf28 integer im,jm,lm,i,j,l,iv,iii,iji,iif,ijf 29 29 30 30 logical writectl … … 59 59 nvar(if)=ivar(if) 60 60 var(ivar(if),if)=name 61 tvar(ivar(if),if)=t itlevar(1:lnblnk(titlevar))61 tvar(ivar(if),if)=trim(titlevar) 62 62 nld(ivar(if),if)=nl 63 63 c print*,'initialisation ecriture de ',var(ivar(if),if) … … 101 101 file=fichier(if) 102 102 c WARNING! on reecrase le fichier .ctl a chaque ecriture 103 open(unit(if),file= file(1:lnblnk(file))//'.ctl'103 open(unit(if),file=trim(file)//'.ctl' 104 104 & ,form='formatted',status='unknown') 105 105 write(unit(if),'(a5,1x,a40)') 106 & 'DSET ','^'// file(1:lnblnk(file))//'.dat'106 & 'DSET ','^'//trim(file)//'.dat' 107 107 108 108 write(unit(if),'(a12)') 'UNDEF 1.0E30' -
LMDZ5/branches/testing/libf/dyn3dpar/bands.F90
r1279 r1665 93 93 SUBROUTINE Set_Bands 94 94 USE parallel 95 #ifdef CPP_ EARTH96 ! Ehouarn: what follows is only related to // physics ; for now only for Earth95 #ifdef CPP_PHYS 96 ! Ehouarn: what follows is only related to // physics 97 97 USE mod_phys_lmdz_para, ONLY : jj_para_begin,jj_para_end 98 98 #endif … … 106 106 enddo 107 107 108 #ifdef CPP_EARTH 109 ! Ehouarn: what follows is only related to // physics; for now only for Earth 108 #ifdef CPP_PHYS 110 109 do i=0,MPI_Size-1 111 110 jj_Nb_physic(i)=jj_para_end(i)-jj_para_begin(i)+1 … … 332 331 subroutine AdjustBands_physic 333 332 use times 334 #ifdef CPP_ EARTH335 ! Ehouarn: what follows is only related to // physics ; for now only for Earth333 #ifdef CPP_PHYS 334 ! Ehouarn: what follows is only related to // physics 336 335 USE mod_phys_lmdz_para, only : klon_mpi_para_nb 337 336 #endif … … 359 358 medium=medium/mpi_size 360 359 NbTot=0 361 #ifdef CPP_EARTH 362 ! Ehouarn: what follows is only related to // physics; for now only for Earth 360 #ifdef CPP_PHYS 363 361 do i=0,mpi_size-1 364 362 Inc(i)=nint(klon_mpi_para_nb(i)*(medium-value(i))/value(i)) -
LMDZ5/branches/testing/libf/dyn3dpar/calfis_p.F
r1407 r1665 27 27 $ pdqfi, 28 28 $ pdpsfi) 29 #ifdef CPP_EARTH 30 ! Ehouarn: For now, calfis_p needs Earth physics 31 c 32 c Auteur : P. Le Van, F. Hourdin 33 c ......... 29 #ifdef CPP_PHYS 30 ! If using physics 34 31 USE dimphy 35 32 USE mod_phys_lmdz_para, mpi_root_xx=>mpi_root … … 146 143 REAL clesphy0( longcles ) 147 144 148 #ifdef CPP_EARTH 145 #ifdef CPP_PHYS 146 ! Ehouarn: for now calfis_p needs some informations from physics to compile 149 147 c Local variables : 150 148 c ----------------- … … 222 220 PARAMETER(ntetaSTD=3) 223 221 REAL rtetaSTD(ntetaSTD) 224 DATA rtetaSTD/350., 380., 405./ 222 DATA rtetaSTD/350., 380., 405./ ! Earth-specific values, beware !! 225 223 REAL PVteta(klon,ntetaSTD) 226 224 … … 489 487 490 488 491 IF (is_sequential) THEN 492 c 489 IF (is_sequential.and.(planet_type=="earth")) THEN 490 #ifdef CPP_PHYS 491 ! PVtheta calls tetalevel, which is in the physics 493 492 cIM calcul PV a teta=350, 380, 405K 494 493 CALL PVtheta(ngridmx,llm,pucov,pvcov,pteta, … … 496 495 $ ntetaSTD,rtetaSTD,PVteta) 497 496 c 497 #endif 498 498 ENDIF 499 499 … … 627 627 c$OMP BARRIER 628 628 629 if (planet_type=="earth") then630 #ifdef CPP_EARTH631 632 629 !$OMP MASTER 633 630 ! write(lunout,*) 'PHYSIQUE AVEC NSPLIT_PHYS=',nsplit_phys … … 639 636 zdqfic_omp(:,:,:)=0. 640 637 638 if (planet_type=="earth") then 639 #ifdef CPP_PHYS 641 640 do isplit=1,nsplit_phys 642 641 … … 687 686 enddo 688 687 688 #endif 689 ! of #ifdef CPP_PHYS 690 endif !of if (planet_type=="earth") 691 689 692 zdufi_omp(:,:)=zdufic_omp(:,:)/nsplit_phys 690 693 zdvfi_omp(:,:)=zdvfic_omp(:,:)/nsplit_phys 691 694 zdtfi_omp(:,:)=zdtfic_omp(:,:)/nsplit_phys 692 695 zdqfi_omp(:,:,:)=zdqfic_omp(:,:,:)/nsplit_phys 693 694 #endif695 endif !of if (planet_type=="earth")696 696 c$OMP BARRIER 697 697 … … 1110 1110 firstcal = .FALSE. 1111 1111 1112 #else 1113 write(lunout,*) 1114 & "calfis_p: for now can only work with parallel physics" 1115 stop 1116 #endif 1117 ! of #ifdef CPP_ EARTH1112 #else 1113 write(lunout,*) 1114 & "calfis_p: for now can only work with parallel physics" 1115 stop 1116 #endif 1117 ! of #ifdef CPP_PHYS 1118 1118 RETURN 1119 1119 END -
LMDZ5/branches/testing/libf/dyn3dpar/ce0l.F90
r1664 r1665 19 19 USE dimphy 20 20 USE comgeomphy 21 USE mod_phys_lmdz_para 21 USE mod_phys_lmdz_para, mpi_root_xx=>mpi_root 22 22 USE mod_const_mpi 23 23 USE infotrac … … 31 31 IMPLICIT NONE 32 32 #ifndef CPP_EARTH 33 #include "iniprint.h" 33 34 WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics' 34 35 #else … … 42 43 #include "temps.h" 43 44 #include "logic.h" 45 #ifdef CPP_MPI 46 include 'mpif.h' 47 #endif 48 44 49 INTEGER, PARAMETER :: longcles=20 50 INTEGER :: ierr 45 51 REAL, DIMENSION(longcles) :: clesphy0 46 52 REAL, DIMENSION(iip1,jjp1) :: masque … … 50 56 CALL conf_gcm( 99, .TRUE. , clesphy0 ) 51 57 58 #ifdef CPP_MPI 52 59 CALL init_mpi 60 #endif 53 61 54 62 CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/)) … … 115 123 END IF 116 124 125 #ifdef CPP_MPI 117 126 !$OMP MASTER 118 CALL finalize_parallel 127 CALL MPI_FINALIZE(ierr) 128 IF (ierr /= 0) CALL abort_gcm('ce0l','Error in MPI_FINALIZE',1) 119 129 !$OMP END MASTER 130 #endif 120 131 121 132 #endif -
LMDZ5/branches/testing/libf/dyn3dpar/comvert.h
r1520 r1665 9 9 & aps(llm),bps(llm),scaleheight 10 10 11 common/comverti/disvert_type 11 common/comverti/disvert_type, pressure_exner 12 12 13 13 real ap ! hybrid pressure contribution at interlayers … … 30 30 ! using 'z2sig.def' (or 'esasig.def) file 31 31 32 logical pressure_exner 33 ! compute pressure inside layers using Exner function, else use mean 34 ! of pressure values at interfaces 35 32 36 !----------------------------------------------------------------------- -
LMDZ5/branches/testing/libf/dyn3dpar/conf_gcm.F
r1664 r1665 167 167 nday = 10 168 168 CALL getin('nday',nday) 169 170 !Config Key = starttime 171 !Config Desc = Heure de depart de la simulation 172 !Config Def = 0 173 !Config Help = Heure de depart de la simulation 174 !Config en jour 175 starttime = 0 176 CALL getin('starttime',starttime) 169 177 170 178 !Config Key = day_step -
LMDZ5/branches/testing/libf/dyn3dpar/control_mod.F90
r1502 r1665 10 10 IMPLICIT NONE 11 11 12 REAL :: periodav 12 REAL :: periodav, starttime 13 13 INTEGER :: nday,day_step,iperiod,iapp_tracvl,nsplit_phys 14 14 INTEGER :: iconser,iecri,dissip_period,iphysiq,iecrimoy -
LMDZ5/branches/testing/libf/dyn3dpar/disvert.F90
r1524 r1665 4 4 5 5 ! Auteur : P. Le Van 6 7 use new_unit_m, only: new_unit 8 use ioipsl, only: getin 6 9 7 10 IMPLICIT NONE … … 26 29 real zk, zkm1, dzk1, dzk2, k0, k1 27 30 28 INTEGER l 31 INTEGER l, unit 29 32 REAL dsigmin 30 33 REAL alpha, beta, deltaz 31 INTEGER iostat32 34 REAL x 33 35 character(len=*),parameter :: modname="disvert" 34 36 37 character(len=6):: vert_sampling 38 ! (allowed values are "param", "tropo", "strato" and "read") 39 35 40 !----------------------------------------------------------------------- 41 42 print *, "Call sequence information: disvert" 36 43 37 44 ! default scaleheight is 8km for earth 38 45 scaleheight=8. 39 46 40 OPEN(99, file='sigma.def', status='old', form='formatted', iostat=iostat) 47 vert_sampling = merge("strato", "tropo ", ok_strato) ! default value 48 call getin('vert_sampling', vert_sampling) 49 print *, 'vert_sampling = ' // vert_sampling 41 50 42 IF (iostat == 0) THEN 43 ! cas 1 on lit les options dans sigma.def: 51 select case (vert_sampling) 52 case ("param") 53 ! On lit les options dans sigma.def: 54 OPEN(99, file='sigma.def', status='old', form='formatted') 44 55 READ(99, *) scaleheight ! hauteur d'echelle 8. 45 56 READ(99, *) deltaz ! epaiseur de la premiere couche 0.04 … … 68 79 69 80 sig(llm+1)=0. 70 71 DO l = 1, llm 72 dsig(l) = sig(l)-sig(l+1) 73 end DO 74 ELSE 75 if (ok_strato) then 76 if (llm==39) then 77 dsigmin=0.3 78 else if (llm==50) then 79 dsigmin=1. 80 else 81 write(lunout,*) trim(modname), & 82 ' ATTENTION discretisation z a ajuster' 83 dsigmin=1. 84 endif 85 write(lunout,*) trim(modname), & 86 ' Discretisation verticale DSIGMIN=',dsigmin 87 endif 88 81 case("tropo") 89 82 DO l = 1, llm 90 83 x = 2*asin(1.) * (l - 0.5) / (llm + 1) 91 92 IF (ok_strato) THEN 93 dsig(l) =(dsigmin + 7. * SIN(x)**2) & 94 *(0.5*(1.-tanh(1.*(x-asin(1.))/asin(1.))))**2 95 ELSE 96 dsig(l) = 1.0 + 7.0 * SIN(x)**2 97 ENDIF 84 dsig(l) = 1.0 + 7.0 * SIN(x)**2 98 85 ENDDO 99 86 dsig = dsig / sum(dsig) … … 102 89 sig(l) = sig(l+1) + dsig(l) 103 90 ENDDO 104 ENDIF 91 case("strato") 92 if (llm==39) then 93 dsigmin=0.3 94 else if (llm==50) then 95 dsigmin=1. 96 else 97 write(lunout,*) trim(modname), ' ATTENTION discretisation z a ajuster' 98 dsigmin=1. 99 endif 100 WRITE(LUNOUT,*) trim(modname), 'Discretisation verticale DSIGMIN=',dsigmin 101 102 DO l = 1, llm 103 x = 2*asin(1.) * (l - 0.5) / (llm + 1) 104 dsig(l) =(dsigmin + 7. * SIN(x)**2) & 105 *(0.5*(1.-tanh(1.*(x-asin(1.))/asin(1.))))**2 106 ENDDO 107 dsig = dsig / sum(dsig) 108 sig(llm+1) = 0. 109 DO l = llm, 1, -1 110 sig(l) = sig(l+1) + dsig(l) 111 ENDDO 112 case("read") 113 call new_unit(unit) 114 open(unit, file="hybrid.txt", status="old", action="read", & 115 position="rewind") 116 read(unit, fmt=*) ! skip title line 117 do l = 1, llm + 1 118 read(unit, fmt=*) sig(l) 119 end do 120 close(unit) 121 case default 122 call abort_gcm("disvert", 'Wrong value for "vert_sampling"', 1) 123 END select 105 124 106 125 DO l=1, llm -
LMDZ5/branches/testing/libf/dyn3dpar/dynetat0.F
r1421 r1665 119 119 day_ini = tab_cntrl(30) 120 120 itau_dyn = tab_cntrl(31) 121 start_time = tab_cntrl(32) 121 122 c ................................................................. 122 123 c -
LMDZ5/branches/testing/libf/dyn3dpar/dynredem.F
r1664 r1665 120 120 tab_cntrl(30) = REAL(iday_end) 121 121 tab_cntrl(31) = REAL(itau_dyn + itaufin) 122 c start_time: start_time of simulation (not necessarily 0.) 123 tab_cntrl(32) = start_time 122 124 c 123 125 c ......................................................... -
LMDZ5/branches/testing/libf/dyn3dpar/dynredem_p.F
r1664 r1665 120 120 tab_cntrl(30) = REAL(iday_end) 121 121 tab_cntrl(31) = REAL(itau_dyn + itaufin) 122 c start_time: start_time of simulation (not necessarily 0.) 123 tab_cntrl(32) = start_time 122 124 c 123 125 c ......................................................... -
LMDZ5/branches/testing/libf/dyn3dpar/etat0_netcdf.F90
r1520 r1665 251 251 !******************************************************************************* 252 252 CALL pression(ip1jmp1, ap, bp, psol, p3d) 253 if ( disvert_type.eq.1) then253 if (pressure_exner) then 254 254 CALL exner_hyb(ip1jmp1, psol, p3d, alpha, beta, pks, pk, y) 255 else ! we assume that we are in the disvert_type==2 case255 else 256 256 CALL exner_milieu(ip1jmp1,psol,p3d,beta,pks,pk,y) 257 257 endif -
LMDZ5/branches/testing/libf/dyn3dpar/exner_hyb.F
r1520 r1665 56 56 ! Sanity check 57 57 if (firstcall) then 58 ! check that vertical discretization is compatible59 ! with this routine60 if (disvert_type.ne.1) then61 call abort_gcm(modname,62 & "this routine should only be called if disvert_type==1",42)63 endif64 65 58 ! sanity checks for Shallow Water case (1 vertical layer) 66 59 if (llm.eq.1) then -
LMDZ5/branches/testing/libf/dyn3dpar/exner_hyb_p.F
r1664 r1665 60 60 ! Sanity check 61 61 if (firstcall) then 62 ! check that vertical discretization is compatible63 ! with this routine64 if (disvert_type.ne.1) then65 call abort_gcm(modname,66 & "this routine should only be called if disvert_type==1",42)67 endif68 69 62 ! sanity checks for Shallow Water case (1 vertical layer) 70 63 if (llm.eq.1) then -
LMDZ5/branches/testing/libf/dyn3dpar/exner_milieu.F
r1520 r1665 53 53 ! Sanity check 54 54 if (firstcall) then 55 ! check that vertical discretization is compatible56 ! with this routine57 if (disvert_type.ne.2) then58 call abort_gcm(modname,59 & "this routine should only be called if disvert_type==2",42)60 endif61 62 55 ! sanity checks for Shallow Water case (1 vertical layer) 63 56 if (llm.eq.1) then -
LMDZ5/branches/testing/libf/dyn3dpar/exner_milieu_p.F
r1664 r1665 56 56 ! Sanity check 57 57 if (firstcall) then 58 ! check that vertical discretization is compatible59 ! with this routine60 if (disvert_type.ne.2) then61 call abort_gcm(modname,62 & "this routine should only be called if disvert_type==2",42)63 endif64 65 58 ! sanity checks for Shallow Water case (1 vertical layer) 66 59 if (llm.eq.1) then -
LMDZ5/branches/testing/libf/dyn3dpar/filtreg_p.F
r1146 r1665 208 208 IF( ifiltre.EQ.-2 ) THEN 209 209 DO j = jdfil,jffil 210 #ifdef BLAS 210 211 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 211 212 & matrinvn(1,1,j), iim, 212 213 & champ_loc(1,j,1), iip1*nlat, 0.0, 213 214 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 215 #else 216 champ_fft(:,j-jdfil+1,:) 217 & =matmul(matrinvn(:,:,j),champ_loc(:iim,j,:)) 218 #endif 214 219 ENDDO 215 220 216 221 ELSE IF ( griscal ) THEN 217 222 DO j = jdfil,jffil 223 #ifdef BLAS 218 224 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 219 225 & matriceun(1,1,j), iim, 220 226 & champ_loc(1,j,1), iip1*nlat, 0.0, 221 227 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 228 #else 229 champ_fft(:,j-jdfil+1,:) 230 & =matmul(matriceun(:,:,j),champ_loc(:iim,j,:)) 231 #endif 222 232 ENDDO 223 233 224 234 ELSE 225 235 DO j = jdfil,jffil 236 #ifdef BLAS 226 237 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 227 238 & matricevn(1,1,j), iim, 228 239 & champ_loc(1,j,1), iip1*nlat, 0.0, 229 240 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 241 #else 242 champ_fft(:,j-jdfil+1,:) 243 & =matmul(matricevn(:,:,j),champ_loc(:iim,j,:)) 244 #endif 230 245 ENDDO 231 246 … … 236 251 IF( ifiltre.EQ.-2 ) THEN 237 252 DO j = jdfil,jffil 253 #ifdef BLAS 238 254 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 239 255 & matrinvs(1,1,j-jfiltsu+1), iim, 240 256 & champ_loc(1,j,1), iip1*nlat, 0.0, 241 257 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 258 #else 259 champ_fft(:,j-jdfil+1,:) 260 & =matmul(matrinvs(:,:,j-jfiltsu+1), 261 & champ_loc(:iim,j,:)) 262 #endif 242 263 ENDDO 243 264 … … 245 266 246 267 DO j = jdfil,jffil 268 #ifdef BLAS 247 269 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 248 270 & matriceus(1,1,j-jfiltsu+1), iim, 249 271 & champ_loc(1,j,1), iip1*nlat, 0.0, 250 272 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 273 #else 274 champ_fft(:,j-jdfil+1,:) 275 & =matmul(matriceus(:,:,j-jfiltsu+1), 276 & champ_loc(:iim,j,:)) 277 #endif 251 278 ENDDO 252 279 … … 254 281 255 282 DO j = jdfil,jffil 283 #ifdef BLAS 256 284 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 257 285 & matricevs(1,1,j-jfiltsv+1), iim, 258 286 & champ_loc(1,j,1), iip1*nlat, 0.0, 259 287 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 288 #else 289 champ_fft(:,j-jdfil+1,:) 290 & =matmul(matricevs(:,:,j-jfiltsv+1), 291 & champ_loc(:iim,j,:)) 292 #endif 260 293 ENDDO 261 294 -
LMDZ5/branches/testing/libf/dyn3dpar/gcm.F
r1664 r1665 20 20 USE control_mod 21 21 22 ! Ehouarn: for now these only apply to Earth: 23 #ifdef CPP_EARTH 22 #ifdef CPP_PHYS 24 23 USE mod_grid_phy_lmdz 25 24 USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb … … 87 86 88 87 REAL zdtvr 89 c INTEGER nbetatmoy, nbetatdem,nbetat90 INTEGER nbetatmoy, nbetatdem91 88 92 89 c variables dynamiques … … 189 186 call ini_getparam("out.def") 190 187 call Read_Distrib 191 ! Ehouarn : temporarily (?) keep this only for Earth 192 if (planet_type.eq."earth") then 193 #ifdef CPP_EARTH 188 189 #ifdef CPP_PHYS 194 190 CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys) 195 191 #endif 196 endif ! of if (planet_type.eq."earth")197 192 CALL set_bands 198 #ifdef CPP_EARTH 199 ! Ehouarn: For now only Earth physics is parallel 193 #ifdef CPP_PHYS 200 194 CALL Init_interface_dyn_phys 201 195 #endif … … 209 203 c$OMP END PARALLEL 210 204 211 ! Ehouarn : temporarily (?) keep this only for Earth 212 if (planet_type.eq."earth") then 213 #ifdef CPP_EARTH 205 #ifdef CPP_PHYS 214 206 c$OMP PARALLEL 215 207 call InitComgeomphy 216 208 c$OMP END PARALLEL 217 209 #endif 218 endif ! of if (planet_type.eq."earth")219 210 220 211 c----------------------------------------------------------------------- … … 323 314 C on remet le calendrier à zero si demande 324 315 c 316 IF (start_time /= starttime) then 317 WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le' 318 &,' fichier restart ne correspond pas à celle lue dans le run.def' 319 IF (raz_date == 1) then 320 WRITE(lunout,*)'Je prends l''heure lue dans run.def' 321 start_time = starttime 322 ELSE 323 WRITE(lunout,*)'Je m''arrete' 324 CALL abort 325 ENDIF 326 ENDIF 325 327 IF (raz_date == 1) THEN 326 328 annee_ref = anneeref … … 390 392 #endif 391 393 392 c nombre d'etats dans les fichiers demarrage et histoire393 nbetatdem = nday / iecri394 nbetatmoy = nday / periodav + 1395 394 396 395 if (iflag_phys.eq.1) then … … 445 444 WRITE(lunout,*) 446 445 . 'GCM: WARNING!!! vitesse verticale nulle dans la physique' 447 ! Earth: 448 if (planet_type.eq."earth") then 449 #ifdef CPP_EARTH 446 ! Physics: 447 #ifdef CPP_PHYS 450 448 CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys , 451 449 , latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp ) 452 450 #endif 453 endif ! of if (planet_type.eq."earth")454 451 call_iniphys=.false. 455 452 ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1)) … … 484 481 301 FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4) 485 482 302 FORMAT('1'/,15x,' au ', i2,'/',i2,'/',i4) 483 #endif 484 485 #ifdef CPP_PHYS 486 ! Create start file (startphy.nc) and boundary conditions (limit.nc) 487 ! for the Earth verstion 488 if (iflag_phys>=100) then 489 call iniaqua(ngridmx,latfi,lonfi,iflag_phys) 490 endif 486 491 #endif 487 492 -
LMDZ5/branches/testing/libf/dyn3dpar/gr_dyn_fi_p.F
r1279 r1665 3 3 ! 4 4 SUBROUTINE gr_dyn_fi_p(nfield,im,jm,ngrid,pdyn,pfi) 5 #ifdef CPP_ EARTH5 #ifdef CPP_PHYS 6 6 ! Interface with parallel physics, 7 ! for now this routine only works with Earth physics8 7 USE mod_interface_dyn_phys 9 8 USE dimphy … … 40 39 ENDDO 41 40 c$OMP END DO NOWAIT 42 #else43 write(lunout,*) "gr_fi_dyn_p : This routine should not be called",44 & "without parallelized physics"45 stop46 41 #endif 47 ! of #ifdef CPP_ EARTH42 ! of #ifdef CPP_PHYS 48 43 RETURN 49 44 END -
LMDZ5/branches/testing/libf/dyn3dpar/gr_fi_dyn_p.F
r1279 r1665 3 3 ! 4 4 SUBROUTINE gr_fi_dyn_p(nfield,ngrid,im,jm,pfi,pdyn) 5 #ifdef CPP_ EARTH5 #ifdef CPP_PHYS 6 6 ! Interface with parallel physics, 7 ! for now this routine only works with Earth physics8 7 USE mod_interface_dyn_phys 9 8 USE dimphy … … 52 51 ENDDO 53 52 c$OMP END DO NOWAIT 54 #else55 write(lunout,*) "gr_fi_dyn_p : This routine should not be called",56 & "without parallelized physics"57 stop58 53 #endif 59 ! of #ifdef CPP_ EARTH54 ! of #ifdef CPP_PHYS 60 55 RETURN 61 56 END -
LMDZ5/branches/testing/libf/dyn3dpar/guide_p_mod.F90
r1520 r1665 455 455 ! Calcul niveaux pression milieu de couches 456 456 CALL pression_p( ip1jmp1, ap, bp, ps, p ) 457 if ( disvert_type==1) then457 if (pressure_exner) then 458 458 CALL exner_hyb_p(ip1jmp1,ps,p,alpha,beta,pks,pk,pkf) 459 459 else … … 755 755 ELSE 756 756 CALL pression_p( ip1jmp1, ap, bp, psi, p ) 757 if ( disvert_type==1) then757 if (pressure_exner) then 758 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 case759 else 760 760 CALL exner_milieu_p(ip1jmp1,psi,p,beta,pks,pk,pkf) 761 761 endif -
LMDZ5/branches/testing/libf/dyn3dpar/iniacademic.F90
r1664 r1665 222 222 223 223 CALL pression ( ip1jmp1, ap, bp, ps, p ) 224 if ( disvert_type.eq.1) then224 if (pressure_exner) then 225 225 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 226 else if (disvert_type.eq.2) then226 else 227 227 call exner_milieu(ip1jmp1,ps,p,beta,pks,pk,pkf) 228 else229 write(abort_message,*) "Wrong value for disvert_type: ", &230 disvert_type231 call abort_gcm(modname,abort_message,0)232 228 endif 233 229 CALL massdair(p,masse) -
LMDZ5/branches/testing/libf/dyn3dpar/inidissip.F90
r1502 r1665 28 28 ! Local variables: 29 29 REAL fact,zvert(llm),zz 30 REAL zh(ip1jmp1),zu(ip1jmp1),zv(ip1jm),deltap(ip1jmp1,llm) 30 REAL zh(ip1jmp1),zu(ip1jmp1), gx(ip1jmp1), divgra(ip1jmp1) 31 real zv(ip1jm), gy(ip1jm), deltap(ip1jmp1,llm) 31 32 REAL ullm,vllm,umin,vmin,zhmin,zhmax 32 REAL zllm ,z1llm33 REAL zllm 33 34 34 35 INTEGER l,ij,idum,ii … … 78 79 DO l = 1,50 79 80 IF(lstardis) THEN 80 CALL divgrad2(1,zh,deltap,niterh, zh)81 CALL divgrad2(1,zh,deltap,niterh,divgra) 81 82 ELSE 82 CALL divgrad (1,zh,niterh, zh)83 CALL divgrad (1,zh,niterh,divgra) 83 84 ENDIF 84 85 85 CALL minmax(iip1*jjp1,zh,zhmin,zhmax ) 86 87 zllm = ABS( zhmax ) 88 z1llm = 1./zllm 89 DO ij = 1,ip1jmp1 90 zh(ij) = zh(ij)* z1llm 91 ENDDO 86 zllm = ABS(maxval(divgra)) 87 zh = divgra / zllm 92 88 ENDDO 93 89 … … 123 119 !cccc CALL covcont( 1,zu,zv,zu,zv ) 124 120 IF(lstardis) THEN 125 CALL gradiv2( 1,zu,zv,nitergdiv, zu,zv)121 CALL gradiv2( 1,zu,zv,nitergdiv,gx,gy ) 126 122 ELSE 127 CALL gradiv ( 1,zu,zv,nitergdiv, zu,zv)123 CALL gradiv ( 1,zu,zv,nitergdiv,gx,gy ) 128 124 ENDIF 129 125 ELSE 130 126 IF(lstardis) THEN 131 CALL nxgraro2( 1,zu,zv,nitergrot, zu,zv)127 CALL nxgraro2( 1,zu,zv,nitergrot,gx,gy ) 132 128 ELSE 133 CALL nxgrarot( 1,zu,zv,nitergrot, zu,zv)129 CALL nxgrarot( 1,zu,zv,nitergrot,gx,gy ) 134 130 ENDIF 135 131 ENDIF 136 132 137 CALL minmax(iip1*jjp1,zu,umin,ullm ) 138 CALL minmax(iip1*jjm, zv,vmin,vllm ) 139 140 ullm = ABS ( ullm ) 141 vllm = ABS ( vllm ) 142 143 zllm = MAX( ullm,vllm ) 144 z1llm = 1./ zllm 145 DO ij = 1, ip1jmp1 146 zu(ij) = zu(ij)* z1llm 147 ENDDO 148 DO ij = 1, ip1jm 149 zv(ij) = zv(ij)* z1llm 150 ENDDO 133 zllm = max(abs(maxval(gx)), abs(maxval(gy))) 134 zu = gx / zllm 135 zv = gy / zllm 151 136 end DO 152 137 -
LMDZ5/branches/testing/libf/dyn3dpar/inigrads.F
r774 r1665 9 9 implicit none 10 10 11 integer if,im,jm,lm,i,j,l ,lnblnk11 integer if,im,jm,lm,i,j,l 12 12 real x(im),y(jm),z(lm),fx,fy,fz,dt 13 13 real xmin,xmax,ymin,ymax … … 40 40 ivar(if)=0 41 41 42 fichier(if)= file(1:lnblnk(file))42 fichier(if)=trim(file) 43 43 44 44 firsttime(if)=.true. … … 70 70 71 71 print*,4*(ifd(if)-iid(if))*(jfd(if)-jid(if)) 72 print*, file(1:lnblnk(file))//'.dat'72 print*,trim(file)//'.dat' 73 73 74 OPEN (unit(if)+1,FILE= file(1:lnblnk(file))//'.dat'74 OPEN (unit(if)+1,FILE=trim(file)//'.dat' 75 75 s ,FORM='unformatted', 76 76 s ACCESS='direct' -
LMDZ5/branches/testing/libf/dyn3dpar/integrd_p.F
r1550 r1665 4 4 SUBROUTINE integrd_p 5 5 $ ( nq,vcovm1,ucovm1,tetam1,psm1,massem1, 6 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps0,masse,phis ,finvmaold)6 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps0,masse,phis) !,finvmaold) 7 7 USE parallel 8 8 USE control_mod, only : planet_type … … 33 33 #include "temps.h" 34 34 #include "serre.h" 35 #include "iniprint.h" 35 36 36 37 c Arguments: 37 38 c ---------- 38 39 39 INTEGER nq 40 41 REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm) 42 REAL q(ip1jmp1,llm,nq) 43 REAL ps0(ip1jmp1),masse(ip1jmp1,llm),phis(ip1jmp1) 44 45 REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm) 46 REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1),massem1(ip1jmp1,llm) 47 48 REAL dv(ip1jm,llm),du(ip1jmp1,llm) 49 REAL dteta(ip1jmp1,llm),dp(ip1jmp1) 50 REAL dq(ip1jmp1,llm,nq), finvmaold(ip1jmp1,llm) 40 integer,intent(in) :: nq ! number of tracers to handle in this routine 41 real,intent(inout) :: vcov(ip1jm,llm) ! covariant meridional wind 42 real,intent(inout) :: ucov(ip1jmp1,llm) ! covariant zonal wind 43 real,intent(inout) :: teta(ip1jmp1,llm) ! potential temperature 44 real,intent(inout) :: q(ip1jmp1,llm,nq) ! advected tracers 45 real,intent(inout) :: ps0(ip1jmp1) ! surface pressure 46 real,intent(inout) :: masse(ip1jmp1,llm) ! atmospheric mass 47 real,intent(in) :: phis(ip1jmp1) ! ground geopotential !!! unused 48 ! values at previous time step 49 real,intent(inout) :: vcovm1(ip1jm,llm) 50 real,intent(inout) :: ucovm1(ip1jmp1,llm) 51 real,intent(inout) :: tetam1(ip1jmp1,llm) 52 real,intent(inout) :: psm1(ip1jmp1) 53 real,intent(inout) :: massem1(ip1jmp1,llm) 54 ! the tendencies to add 55 real,intent(in) :: dv(ip1jm,llm) 56 real,intent(in) :: du(ip1jmp1,llm) 57 real,intent(in) :: dteta(ip1jmp1,llm) 58 real,intent(in) :: dp(ip1jmp1) 59 real,intent(in) :: dq(ip1jmp1,llm,nq) !!! unused 60 ! real,intent(out) :: finvmaold(ip1jmp1,llm) !!! unused 51 61 52 62 c Local: … … 54 64 55 65 REAL vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1) 56 REAL massescr( ip1jmp1,llm ), finvmasse(ip1jmp1,llm) 66 REAL massescr( ip1jmp1,llm ) 67 ! REAL finvmasse(ip1jmp1,llm) 57 68 REAL,SAVE :: p(ip1jmp1,llmp1) 58 69 REAL tpn,tps,tppn(iim),tpps(iim) … … 60 71 REAL,SAVE :: deltap( ip1jmp1,llm ) 61 72 62 INTEGER l,ij,iq 73 INTEGER l,ij,iq,i,j 63 74 64 75 REAL SSUM … … 126 137 127 138 IF( .NOT. checksum ) THEN 128 PRINT*,' Au point ij = ',stop_it, ' , pression sol neg. ' 129 & , ps(stop_it) 130 print *, ' dans integrd' 131 stop 1 139 write(lunout,*) "integrd: negative surface pressure ", 140 & ps(stop_it) 141 write(lunout,*) " at node ij =", stop_it 142 ! since ij=j+(i-1)*jjp1 , we have 143 j=modulo(stop_it,jjp1) 144 i=1+(stop_it-j)/jjp1 145 write(lunout,*) " lon = ",rlonv(i)*180./pi, " deg", 146 & " lat = ",rlatu(j)*180./pi, " deg" 132 147 ENDIF 133 148 … … 167 182 CALL massdair_p ( p , masse ) 168 183 169 c CALL SCOPY( ijp1llm , masse, 1, finvmasse, 1 ) 170 ijb=ij_begin 171 ije=ij_end 172 173 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 174 DO l = 1,llm 175 finvmasse(ijb:ije,l)=masse(ijb:ije,l) 176 ENDDO 177 c$OMP END DO NOWAIT 178 179 jjb=jj_begin 180 jje=jj_end 181 CALL filtreg_p( finvmasse,jjb,jje, jjp1, llm, -2, 2, .TRUE., 1 ) 184 ! Ehouarn : we don't use/need finvmaold and finvmasse, 185 ! so might as well not compute them 186 !c CALL SCOPY( ijp1llm , masse, 1, finvmasse, 1 ) 187 ! ijb=ij_begin 188 ! ije=ij_end 189 ! 190 !c$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 191 ! DO l = 1,llm 192 ! finvmasse(ijb:ije,l)=masse(ijb:ije,l) 193 ! ENDDO 194 !c$OMP END DO NOWAIT 195 ! 196 ! jjb=jj_begin 197 ! jje=jj_end 198 ! CALL filtreg_p( finvmasse,jjb,jje, jjp1, llm, -2, 2, .TRUE., 1 ) 182 199 c 183 200 … … 330 347 ENDIF 331 348 332 c CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 ) 333 334 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 335 DO l = 1, llm 336 finvmaold(ijb:ije,l)=finvmasse(ijb:ije,l) 337 ENDDO 338 c$OMP END DO NOWAIT 349 ! Ehouarn: forget about finvmaold 350 !c CALL SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 ) 351 ! 352 !c$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 353 ! DO l = 1, llm 354 ! finvmaold(ijb:ije,l)=finvmasse(ijb:ije,l) 355 ! ENDDO 356 !c$OMP END DO NOWAIT 339 357 340 358 endif ! of if (planet_type.eq."earth") -
LMDZ5/branches/testing/libf/dyn3dpar/leapfrog_p.F
r1664 r1665 75 75 76 76 real zqmin,zqmax 77 INTEGER nbetatmoy, nbetatdem,nbetat78 77 79 78 c variables dynamiques … … 125 124 REAL SSUM 126 125 REAL time_0 127 REAL,SAVE :: finvmaold(ip1jmp1,llm)126 ! REAL,SAVE :: finvmaold(ip1jmp1,llm) 128 127 129 128 cym LOGICAL lafin … … 234 233 dq(:,:,:)=0. 235 234 CALL pression ( ip1jmp1, ap, bp, ps, p ) 236 if ( disvert_type==1) then235 if (pressure_exner) then 237 236 CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 238 else ! we assume that we are in the disvert_type==2 case237 else 239 238 CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf ) 240 239 endif … … 245 244 c et du parallelisme !! 246 245 247 1 CONTINUE 248 249 jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec) 250 jH_cur = jH_ref + & 251 & (itau * dtvr / daysec - int(itau * dtvr / daysec)) 246 1 CONTINUE ! Matsuno Forward step begins here 247 248 jD_cur = jD_ref + day_ini - day_ref + & 249 & itau/day_step 250 jH_cur = jH_ref + start_time + & 251 & mod(itau,day_step)/float(day_step) 252 if (jH_cur > 1.0 ) then 253 jD_cur = jD_cur +1. 254 jH_cur = jH_cur -1. 255 endif 252 256 253 257 … … 280 284 massem1= masse 281 285 psm1= ps 282 283 finvmaold = masse 284 CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 ) 286 287 ! Ehouarn: finvmaold is actually not used 288 ! finvmaold = masse 289 ! CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 ) 285 290 c$OMP END MASTER 286 291 c$OMP BARRIER … … 300 305 tetam1 (ijb:ije,l) = teta (ijb:ije,l) 301 306 massem1 (ijb:ije,l) = masse (ijb:ije,l) 302 finvmaold(ijb:ije,l)=masse(ijb:ije,l)307 ! finvmaold(ijb:ije,l)=masse(ijb:ije,l) 303 308 304 309 if (pole_sud) ije=ij_end-iip1 … … 309 314 c$OMP ENDDO 310 315 311 312 CALL filtreg_p ( finvmaold ,jj_begin,jj_end,jjp1,313 . llm, -2,2, .TRUE., 1 )316 ! Ehouarn: finvmaold not used 317 ! CALL filtreg_p ( finvmaold ,jj_begin,jj_end,jjp1, 318 ! . llm, -2,2, .TRUE., 1 ) 314 319 315 320 endif ! of if (FirstCaldyn) … … 327 332 cym call minmax(ijp1llm,q(:,:,3),zqmin,zqmax) 328 333 329 2 CONTINUE 334 2 CONTINUE ! Matsuno backward or leapfrog step begins here 330 335 331 336 c$OMP MASTER … … 472 477 call Register_SwapFieldHallo(phi,phi,ip1jmp1,llm, 473 478 & jj_Nb_caldyn,0,0,TestRequest) 474 call Register_SwapFieldHallo(finvmaold,finvmaold,ip1jmp1,llm,475 & jj_Nb_caldyn,0,0,TestRequest)479 ! call Register_SwapFieldHallo(finvmaold,finvmaold,ip1jmp1,llm, 480 ! & jj_Nb_caldyn,0,0,TestRequest) 476 481 477 482 do j=1,nqtot … … 555 560 call start_timer(timer_caldyn) 556 561 562 ! compute geopotential phi() 557 563 CALL geopot_p ( ip1jmp1, teta , pk , pks, phis , phi ) 558 564 … … 629 635 630 636 CALL integrd_p ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 , 631 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,632 $ finvmaold )637 $ dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ) 638 ! $ finvmaold ) 633 639 634 640 ! CALL FTRACE_REGION_END("integrd") … … 693 699 694 700 c$OMP BARRIER 695 if ( disvert_type==1) then701 if (pressure_exner) then 696 702 CALL exner_hyb_p( ip1jmp1, ps, p,alpha,beta,pks, pk, pkf ) 697 else ! we assume that we are in the disvert_type==2 case703 else 698 704 CALL exner_milieu_p( ip1jmp1, ps, p, beta, pks, pk, pkf ) 699 705 endif 700 706 c$OMP BARRIER 701 707 jD_cur = jD_ref + day_ini - day_ref 702 $ + i nt (itau * dtvr / daysec)703 jH_cur = jH_ref + 704 & (itau * dtvr / daysec - int(itau * dtvr / daysec))708 $ + itau/day_step 709 jH_cur = jH_ref + start_time + & 710 & mod(itau,day_step)/float(day_step) 705 711 ! call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes) 712 if (jH_cur > 1.0 ) then 713 jD_cur = jD_cur +1. 714 jH_cur = jH_cur -1. 715 endif 706 716 707 717 c rajout debug … … 719 729 ! Ehouarn: be careful, diagedyn is Earth-specific (includes ../phylmd/..)! 720 730 IF (planet_type.eq."earth") THEN 731 #ifdef CPP_EARTH 721 732 CALL diagedyn(ztit,2,1,1,dtphys 722 733 & , ucov , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2)) 734 #endif 723 735 ENDIF 724 736 ENDIF … … 1036 1048 CALL pression_p ( ip1jmp1, ap, bp, ps, p ) 1037 1049 c$OMP BARRIER 1038 if ( disvert_type==1) then1050 if (pressure_exner) then 1039 1051 CALL exner_hyb_p( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf ) 1040 else ! we assume that we are in the disvert_type==2 case1052 else 1041 1053 CALL exner_milieu_p( ip1jmp1, ps, p, beta, pks, pk, pkf ) 1042 1054 endif … … 1185 1197 c$OMP END DO NOWAIT 1186 1198 1199 if (1 == 0) then 1200 !!! Ehouarn: lines here 1) kill 1+1=2 in the dynamics 1201 !!! 2) should probably not be here anyway 1202 !!! but are kept for those who would want to revert to previous behaviour 1187 1203 c$OMP MASTER 1188 1204 DO ij = 1,iim … … 1195 1211 ENDDO 1196 1212 c$OMP END MASTER 1197 endif 1213 endif ! of if (1 == 0) 1214 endif ! of of (pole_nord) 1198 1215 1199 1216 if (pole_sud) then … … 1211 1228 c$OMP END DO NOWAIT 1212 1229 1230 if (1 == 0) then 1231 !!! Ehouarn: lines here 1) kill 1+1=2 in the dynamics 1232 !!! 2) should probably not be here anyway 1233 !!! but are kept for those who would want to revert to previous behaviour 1213 1234 c$OMP MASTER 1214 1235 DO ij = 1,iim … … 1221 1242 ENDDO 1222 1243 c$OMP END MASTER 1223 endif 1244 endif ! of if (1 == 0) 1245 endif ! of if (pole_sud) 1224 1246 1225 1247 … … 1431 1453 c$OMP BARRIER 1432 1454 c$OMP MASTER 1433 nbetat = nbetatdem1434 1455 CALL geopot_p(ip1jmp1,teta,pk,pks,phis,phi) 1435 1456 … … 1634 1655 c$OMP BARRIER 1635 1656 c$OMP MASTER 1636 nbetat = nbetatdem1637 1657 CALL geopot_p(ip1jmp1,teta,pk,pks,phis,phi) 1638 1658 -
LMDZ5/branches/testing/libf/dyn3dpar/mod_interface_dyn_phys.F90
r1279 r1665 7 7 8 8 9 #ifdef CPP_ EARTH9 #ifdef CPP_PHYS 10 10 ! Interface with parallel physics, 11 ! for now this routine only works with Earth physics12 11 CONTAINS 13 12 … … 56 55 END SUBROUTINE Init_interface_dyn_phys 57 56 #endif 58 ! of #ifdef CPP_ EARTH57 ! of #ifdef CPP_PHYS 59 58 END MODULE mod_interface_dyn_phys -
LMDZ5/branches/testing/libf/dyn3dpar/temps.h
r1279 r1665 14 14 15 15 COMMON/temps/itaufin, dt, day_ini, day_end, annee_ref, day_ref, & 16 & itau_dyn, itau_phy, jD_ref, jH_ref, calend 16 & itau_dyn, itau_phy, jD_ref, jH_ref, calend, & 17 & start_time 18 17 19 18 20 INTEGER itaufin 19 21 INTEGER itau_dyn, itau_phy 20 22 INTEGER day_ini, day_end, annee_ref, day_ref 21 REAL dt, jD_ref, jH_ref 23 REAL dt, jD_ref, jH_ref, start_time 22 24 CHARACTER (len=10) :: calend 23 25 -
LMDZ5/branches/testing/libf/dyn3dpar/wrgrads.F
r774 r1665 22 22 c local 23 23 24 integer im,jm,lm,i,j,l, lnblnk,iv,iii,iji,iif,ijf24 integer im,jm,lm,i,j,l,iv,iii,iji,iif,ijf 25 25 26 26 logical writectl … … 55 55 nvar(if)=ivar(if) 56 56 var(ivar(if),if)=name 57 tvar(ivar(if),if)=t itlevar(1:lnblnk(titlevar))57 tvar(ivar(if),if)=trim(titlevar) 58 58 nld(ivar(if),if)=nl 59 59 print*,'initialisation ecriture de ',var(ivar(if),if) … … 96 96 file=fichier(if) 97 97 c WARNING! on reecrase le fichier .ctl a chaque ecriture 98 open(unit(if),file= file(1:lnblnk(file))//'.ctl'98 open(unit(if),file=trim(file)//'.ctl' 99 99 & ,form='formatted',status='unknown') 100 100 write(unit(if),'(a5,1x,a40)') 101 & 'DSET ','^'// file(1:lnblnk(file))//'.dat'101 & 'DSET ','^'//trim(file)//'.dat' 102 102 103 103 write(unit(if),'(a12)') 'UNDEF 1.0E30' -
LMDZ5/branches/testing/libf/filtrez/coefils.h
r1146 r1665 1 1 ! 2 ! $ Header$2 ! $Id $ 3 3 ! 4 4 COMMON/coefils/jfiltnu,jfiltsu,jfiltnv,jfiltsv,sddu(iim),sddv(iim)& … … 7 7 & ,coefilu2(iim,jjm),coefilv2(iim,jjm) 8 8 !c 9 INTEGER jfiltnu,jfiltsu,jfiltnv,jfiltsv,modfrstu,modfrstv 9 INTEGER jfiltnu ! index of the last lat line filtered in NH (U grid) 10 INTEGER jfiltsu ! index of the first lat line filtered in SH (U grid) 11 INTEGER jfiltnv ! index of the last lat line filtered in NH (V grid) 12 INTEGER jfiltsv ! index of the first lat line filtered in SH (V grid) 13 INTEGER modfrstu ! number of retained (ie: unfiltered) modes on U grid 14 INTEGER modfrstv ! number of retained (ie: unfiltered) modes on V grid 10 15 REAL sddu,sddv,unsddu,unsddv,coefilu,coefilv,eignfnu,eignfnv 11 16 REAL coefilu2,coefilv2 -
LMDZ5/branches/testing/libf/filtrez/filtreg_mod.F90
r1279 r1665 1 ! 2 ! $Id $ 3 ! 1 4 MODULE filtreg_mod 2 5 … … 42 45 INTEGER ixmineq 43 46 #endif 44 EXTERNAL inifgn45 47 ! 46 48 ! ------------------------------------------------------------ … … 71 73 CALL inifgn(eignvl) 72 74 ! 73 PRINT *,' EIGNVL '75 PRINT *,'inifilr: EIGNVL ' 74 76 PRINT 250,eignvl 75 250 FORMAT( 1x,5e1 3.6)77 250 FORMAT( 1x,5e14.6) 76 78 ! 77 79 ! compute eigenvalues and eigenfunctions … … 113 115 #endif 114 116 ! 117 ! For a regular grid, we want the filter to start at latitudes 118 ! corresponding to lengths dx of the same size as dy (in terms 119 ! of angles: dx=2*dy) => at colat0=0.5 (i.e. colatitude=30 degrees 120 ! <=> latitude=60 degrees). 121 ! Same idea for the zoomed grid: start filtering polewards as soon 122 ! as length dx becomes of the same size as dy 115 123 ! 116 124 colat0 = MIN( 0.5, dymin/dxmin ) … … 158 166 imx = iim 159 167 ! 160 PRINT *,' TRUNCATION AT ',imx 161 ! 168 PRINT *,'inifilr: TRUNCATION AT ',imx 169 ! 170 ! Ehouarn: set up some defaults 171 jfiltnu=2 ! avoid north pole 172 jfiltsu=jjm ! avoid south pole (which is at jjm+1) 173 jfiltnv=1 ! NB: no poles on the V grid 174 jfiltsv=jjm 175 162 176 DO j = 2, jjm/2+1 163 177 cof = COS( rlatu(j) )/ colat0 164 178 IF ( cof .LT. 1. ) THEN 165 IF( rlamda(imx) * COS(rlatu(j) ).LT.1. ) jfiltnu= j 179 IF( rlamda(imx) * COS(rlatu(j) ).LT.1. ) THEN 180 jfiltnu= j 181 ENDIF 166 182 ENDIF 167 183 168 184 cof = COS( rlatu(jjp1-j+1) )/ colat0 169 185 IF ( cof .LT. 1. ) THEN 170 IF( rlamda(imx) * COS(rlatu(jjp1-j+1) ).LT.1. ) &186 IF( rlamda(imx) * COS(rlatu(jjp1-j+1) ).LT.1. ) THEN 171 187 jfiltsu= jjp1-j+1 188 ENDIF 172 189 ENDIF 173 190 ENDDO … … 176 193 cof = COS( rlatv(j) )/ colat0 177 194 IF ( cof .LT. 1. ) THEN 178 IF( rlamda(imx) * COS(rlatv(j) ).LT.1. ) jfiltnv= j 195 IF( rlamda(imx) * COS(rlatv(j) ).LT.1. ) THEN 196 jfiltnv= j 197 ENDIF 179 198 ENDIF 180 199 181 200 cof = COS( rlatv(jjm-j+1) )/ colat0 182 201 IF ( cof .LT. 1. ) THEN 183 IF( rlamda(imx) * COS(rlatv(jjm-j+1) ).LT.1. ) &202 IF( rlamda(imx) * COS(rlatv(jjm-j+1) ).LT.1. ) THEN 184 203 jfiltsv= jjm-j+1 204 ENDIF 185 205 ENDIF 186 206 ENDDO 187 207 ! 188 208 189 IF ( jfiltnu.LE.0 ) jfiltnu=1190 209 IF( jfiltnu.GT. jjm/2 +1 ) THEN 191 210 PRINT *,' jfiltnu en dehors des valeurs acceptables ' ,jfiltnu … … 193 212 ENDIF 194 213 195 IF( jfiltsu.LE.0) jfiltsu=1196 214 IF( jfiltsu.GT. jjm +1 ) THEN 197 215 PRINT *,' jfiltsu en dehors des valeurs acceptables ' ,jfiltsu … … 199 217 ENDIF 200 218 201 IF( jfiltnv.LE.0) jfiltnv=1202 219 IF( jfiltnv.GT. jjm/2 ) THEN 203 220 PRINT *,' jfiltnv en dehors des valeurs acceptables ' ,jfiltnv … … 205 222 ENDIF 206 223 207 IF( jfiltsv.LE.0) jfiltsv=1208 224 IF( jfiltsv.GT. jjm ) THEN 209 225 PRINT *,' jfiltsv en dehors des valeurs acceptables ' ,jfiltsv … … 211 227 ENDIF 212 228 213 PRINT *,' jfiltnv jfiltsv jfiltnu jfiltsu ' , &229 PRINT *,'inifilr: jfiltnv jfiltsv jfiltnu jfiltsu ' , & 214 230 jfiltnv,jfiltsv,jfiltnu,jfiltsu 215 231 216 232 IF(first_call_inifilr) THEN 217 233 ALLOCATE(matriceun(iim,iim,jfiltnu)) 218 ALLOCATE(matriceus(iim,iim,j filtsu))234 ALLOCATE(matriceus(iim,iim,jjm-jfiltsu+1)) 219 235 ALLOCATE(matricevn(iim,iim,jfiltnv)) 220 ALLOCATE(matricevs(iim,iim,j filtsv))236 ALLOCATE(matricevs(iim,iim,jjm-jfiltsv+1)) 221 237 ALLOCATE( matrinvn(iim,iim,jfiltnu)) 222 ALLOCATE( matrinvs(iim,iim,j filtsu))238 ALLOCATE( matrinvs(iim,iim,jjm-jfiltsu+1)) 223 239 first_call_inifilr = .FALSE. 224 240 ENDIF … … 230 246 ! 231 247 DO j = 1,jjm 248 !default initialization: all modes are retained (i.e. no filtering) 232 249 modfrstu( j ) = iim 233 250 modfrstv( j ) = iim … … 306 323 307 324 IF(jfiltnv.GE.jjm/2 .OR. jfiltnu.GE.jjm/2)THEN 308 325 ! Ehouarn: and what are these for??? Trying to handle a limit case 326 ! where filters extend to and meet at the equator? 309 327 IF(jfiltnv.EQ.jfiltsv)jfiltsv=1+jfiltnv 310 328 IF(jfiltnu.EQ.jfiltsu)jfiltsu=1+jfiltnu … … 334 352 eignft(i,k) = eignfnv(k,i) * coff 335 353 ENDDO 336 ENDDO 354 ENDDO ! of DO i=1,iim 337 355 #ifdef CRAY 338 356 CALL MXM( eignfnv,iim,eignft,iim,matriceun(1,1,j),iim ) … … 350 368 ENDDO 351 369 ENDDO 352 ENDDO 353 #endif 354 #endif 355 356 ENDDO 370 ENDDO ! of DO k = 1, iim 371 #endif 372 #endif 373 374 ENDDO ! of DO j = 2, jfiltnu 357 375 358 376 DO j = jfiltsu, jjm … … 364 382 eignft(i,k) = eignfnv(k,i) * coff 365 383 ENDDO 366 ENDDO 384 ENDDO ! of DO i=1,iim 367 385 #ifdef CRAY 368 386 CALL MXM(eignfnv,iim,eignft,iim,matriceus(1,1,j-jfiltsu+1),iim) … … 381 399 ENDDO 382 400 ENDDO 383 ENDDO 384 #endif 385 #endif 386 387 ENDDO 401 ENDDO ! of DO k = 1, iim 402 #endif 403 #endif 404 405 ENDDO ! of DO j = jfiltsu, jjm 388 406 389 407 ! ................................................................... … … 421 439 #endif 422 440 423 ENDDO 441 ENDDO ! of DO j = 1, jfiltnv 424 442 425 443 DO j = jfiltsv, jjm … … 452 470 #endif 453 471 454 ENDDO 472 ENDDO ! of DO j = jfiltsv, jjm 455 473 456 474 ! ................................................................... … … 488 506 #endif 489 507 490 ENDDO 508 ENDDO ! of DO j = 2, jfiltnu 491 509 492 510 DO j = jfiltsu, jjm … … 518 536 #endif 519 537 520 ENDDO 538 ENDDO ! of DO j = jfiltsu, jjm 521 539 522 540 IF (use_filtre_fft) THEN -
LMDZ5/branches/testing/libf/grid/dimension/makdim
r1146 r1665 1 for i in $* ; do 2 list=$list.$i 1 #!/bin/bash 2 #set -xv 3 4 # sanity check: do we have the required argument ? 5 if (( $# < 1 )) || (( $# > 3 )) 6 then 7 echo "Wrong number of parameters in $0 !!!" 8 echo " Usage:" 9 echo " $0 [im] [jm] lm" 10 echo " where im, jm and lm are the dimensions" 11 exit 12 fi 13 14 # build "fichnom", the relevant 'dimensions.im.jm.lm' file name 15 for i in $* 16 do 17 list=$list.$i 3 18 done 4 19 fichdim=dimensions${list} 5 20 6 if [ ! -f $fichdim ] ; then 7 # si le fichier de dimensions n'existe pas, on le cree 21 if [ ! -f $fichdim ] 22 then 23 # echo "$fichdim does not exist" 8 24 9 if [ $# -ge 3 ] ; then 10 im=$1 11 jm=$2 12 lm=$3 13 n2=$1 14 ndm=1 25 # assign values of im, jm and lm 26 if [ $# -ge 3 ] 27 then 28 im=$1 29 jm=$2 30 lm=$3 31 ndm=1 32 elif [ $# -ge 2 ] 33 then 34 im=1 35 jm=$1 36 lm=$2 37 ndm=1 38 elif [ $# -ge 1 ] 39 then 40 im=1 41 jm=1 42 lm=$1 43 ndm=1 44 fi 15 45 16 # Le test suivant est commente car il est inutile avec le nouveau 17 # filtre filtrez. Attention avec le "vieux" filtre (F. Forget,11/1994) 18 # 19 # while [ "$n2" -gt 2 ]; do 20 # n2=`expr $n2 / 2` 21 # ndm=`expr $ndm + 1` 22 # echo $n2 23 # done 24 # if [ "$n2" != 2 ] ; then 25 # echo le nombre de longitude doit etre une puissance de 2 26 # exit 27 # fi 28 29 30 else if [ $# -ge 2 ] ; then 31 im=1 32 jm=$1 33 lm=$2 34 ndm=1 35 else if [ $# -ge 1 ] ; then 36 im=1 37 jm=1 38 lm=$1 39 ndm=1 40 else 41 echo il faut au moins une dimension 42 exit 43 fi 44 fi 45 fi 46 46 # since the file doesn't exist, we create it 47 47 cat << EOF > $fichdim 48 48 !----------------------------------------------------------------------- … … 62 62 fi 63 63 64 # remove 'old' dimensions.h file (if any) and replace it with new one 65 if [ -f ../dimensions.h ] ; then 64 66 \rm ../dimensions.h 67 fi 65 68 tar cf - $fichdim | ( cd .. ; tar xf - ; mv $fichdim dimensions.h ) 69 # line above is a trick to preserve time of creation of dimensions.h files -
LMDZ5/branches/testing/libf/phylmd/calwake.F
r1403 r1665 60 60 REAL wake_dtKE(klon,klev),wake_dqKE(klon,klev) 61 61 REAL wake_dtPBL(klon,klev),wake_dqPBL(klon,klev) 62 REAL wake_omg(klon,klev +1),wake_dp_deltomg(klon,klev)62 REAL wake_omg(klon,klev),wake_dp_deltomg(klon,klev) 63 63 REAL wake_spread(klon,klev),wake_Cstar(klon) 64 64 REAL wake_ddeltat(klon,klev),wake_ddeltaq(klon,klev) … … 84 84 REAL tu(klon,klev),qu(klon,klev) 85 85 REAL hw(klon),sigmaw(klon),wape(klon),fip(klon),gfl(klon) 86 REAL omgbdth(klon,klev ),dp_omgb(klon,klev)86 REAL omgbdth(klon,klev+1),dp_omgb(klon,klev) 87 87 REAL dtKE(klon,klev),dqKE(klon,klev) 88 88 REAL dtPBL(klon,klev),dqPBL(klon,klev) -
LMDZ5/branches/testing/libf/phylmd/climb_hq_mod.F90
r1084 r1665 252 252 Bcoef(i) = -1. * RG / buf 253 253 END DO 254 acoef(knon+1: klon) = 0. 255 bcoef(knon+1: klon) = 0. 254 256 255 257 END SUBROUTINE calc_coef -
LMDZ5/branches/testing/libf/phylmd/climb_wind_mod.F90
r1067 r1665 209 209 Bcoef(i) = -RG/buf 210 210 END DO 211 acoef(knon+1: klon) = 0. 212 bcoef(knon+1: klon) = 0. 211 213 212 214 END SUBROUTINE calc_coef -
LMDZ5/branches/testing/libf/phylmd/coef_diff_turb_mod.F90
r1067 r1665 389 389 ! calculer la fraction nuageuse (processus humide): 390 390 ! 391 zfr = (zq+ratqs*zq-zqs) / (2.0*ratqs*zq) 391 if (zq /= 0.) then 392 zfr = (zq+ratqs*zq-zqs) / (2.0*ratqs*zq) 393 else 394 zfr = 0. 395 end if 392 396 zfr = MAX(0.0,MIN(1.0,zfr)) 393 397 IF (.NOT.richum) zfr = 0.0 -
LMDZ5/branches/testing/libf/phylmd/concvl.F
r1664 r1665 248 248 DO i = 1, klon 249 249 cbmf(i) = 0. 250 plcl(i) = 0.250 ! plcl(i) = 0. 251 251 sigd(i) = 0. 252 252 ENDDO … … 256 256 plfc(:) = 0. 257 257 wbeff(:) = 100. 258 plcl(:) = 0. 258 259 259 260 DO k = 1, klev+1 -
LMDZ5/branches/testing/libf/phylmd/cpl_mod.F90
r1454 r1665 345 345 IF (is_sequential) THEN 346 346 ndexcs(:) = 0 347 itau_w = itau_phy + itime 347 itau_w = itau_phy + itime + start_time * day_step / iphysiq 348 348 DO i = 1, maxrecv 349 349 IF (inforecv(i)%action) THEN … … 1232 1232 IF (is_sequential) THEN 1233 1233 ndexct(:) = 0 1234 itau_w = itau_phy + itime 1234 itau_w = itau_phy + itime + start_time * day_step / iphysiq 1235 1235 CALL histwrite(nidct,'tauxe',itau_w,tmp_taux,iim*(jjm+1),ndexct) 1236 1236 CALL histwrite(nidct,'tauyn',itau_w,tmp_tauy,iim*(jjm+1),ndexct) -
LMDZ5/branches/testing/libf/phylmd/iostart.F90
r1403 r1665 177 177 ierr=NF90_GET_VAR(nid_start,varid,field_glo) 178 178 IF (ierr/=NF90_NOERR) THEN 179 ! La variable exist dans le fichier mais la lecture a echouee. 179 180 PRINT*, 'phyetat0: Lecture echouee pour <'//field_name//'>' 180 CALL abort 181 182 IF (field_name=='CLWCON' .OR. field_name=='RNEBCON' .OR. field_name=='RATQS') THEN 183 ! Essaye de lire le variable sur surface uniqument, comme fait avant 184 field_glo(:)=0. 185 ierr=NF90_GET_VAR(nid_start,varid,field_glo(1:klon_glo)) 186 IF (ierr/=NF90_NOERR) THEN 187 PRINT*, 'phyetat0: Lecture echouee aussi en 2D pour <'//field_name//'>' 188 CALL abort 189 ELSE 190 PRINT*, 'phyetat0: La variable <'//field_name//'> lu sur surface seulement'!, selon ancien format, le reste mis a zero' 191 END IF 192 ELSE 193 CALL abort 194 ENDIF 181 195 ENDIF 182 196 -
LMDZ5/branches/testing/libf/phylmd/limit_read_mod.F90
r1001 r1665 150 150 151 151 INCLUDE "indicesol.h" 152 INCLUDE "iniprint.h" 152 153 153 154 ! In- and ouput arguments … … 165 166 !$OMP THREADPRIVATE(lmt_pas) 166 167 LOGICAL, SAVE :: first_call=.TRUE. 167 !$OMP THREADPRIVATE(first_call) 168 !$OMP THREADPRIVATE(first_call) 169 INTEGER, SAVE :: jour_lu = -1 170 !$OMP THREADPRIVATE(jour_lu) 168 171 ! Locals variables 169 172 !**************************************************************************************** … … 209 212 210 213 is_modified = .FALSE. 211 IF (MOD(itime-1, lmt_pas) == 0) THEN ! time to read 214 IF (MOD(itime-1, lmt_pas) == 0 .OR. jour_lu /= jour ) THEN ! time to read 215 jour_lu = jour 212 216 is_modified = .TRUE. 213 217 !$OMP MASTER ! Only master thread -
LMDZ5/branches/testing/libf/phylmd/phyetat0.F
r1458 r1665 749 749 ENDIF 750 750 751 u_ancien = 0.0 !AXC: We don't have u_ancien and v_ancien in the start 752 v_ancien = 0.0 !AXC: files, therefore they have to be initialized. 753 c 751 CALL get_field("UANCIEN",u_ancien,found) 752 IF (.NOT. found) THEN 753 PRINT*, "phyetat0: Le champ <UANCIEN> est absent" 754 PRINT*, "Depart legerement fausse. Mais je continue" 755 ancien_ok = .FALSE. 756 ENDIF 757 758 CALL get_field("VANCIEN",v_ancien,found) 759 IF (.NOT. found) THEN 760 PRINT*, "phyetat0: Le champ <VANCIEN> est absent" 761 PRINT*, "Depart legerement fausse. Mais je continue" 762 ancien_ok = .FALSE. 763 ENDIF 754 764 755 765 clwcon=0. 756 CALL get_field("CLWCON",clwcon (:,1),found)766 CALL get_field("CLWCON",clwcon,found) 757 767 IF (.NOT. found) THEN 758 768 PRINT*, "phyetat0: Le champ CLWCON est absent" … … 766 776 c 767 777 rnebcon = 0. 768 CALL get_field("RNEBCON",rnebcon (:,1),found)778 CALL get_field("RNEBCON",rnebcon,found) 769 779 IF (.NOT. found) THEN 770 780 PRINT*, "phyetat0: Le champ RNEBCON est absent" … … 781 791 c 782 792 ratqs=0. 783 CALL get_field("RATQS",ratqs (:,1),found)793 CALL get_field("RATQS",ratqs,found) 784 794 IF (.NOT. found) THEN 785 795 PRINT*, "phyetat0: Le champ <RATQS> est absent" -
LMDZ5/branches/testing/libf/phylmd/phyredem.F
r1458 r1665 267 267 268 268 CALL put_field("QANCIEN","QANCIEN",q_ancien) 269 269 270 CALL put_field("UANCIEN","",u_ancien) 271 272 CALL put_field("VANCIEN","",v_ancien) 273 270 274 CALL put_field("RUGMER","Longueur de rugosite sur mer", 271 275 . frugs(:,is_oce)) 272 276 273 CALL put_field("CLWCON","Eau liquide convective",clwcon (:,1))274 275 CALL put_field("RNEBCON","Nebulosite convective",rnebcon (:,1))276 277 CALL put_field("RATQS", "Ratqs",ratqs (:,1))277 CALL put_field("CLWCON","Eau liquide convective",clwcon) 278 279 CALL put_field("RNEBCON","Nebulosite convective",rnebcon) 280 281 CALL put_field("RATQS", "Ratqs",ratqs) 278 282 c 279 283 c run_off_lic_0 -
LMDZ5/branches/testing/libf/phylmd/phys_output_mod.F90
r1664 r1665 1318 1318 ! Couplage conv-CL 1319 1319 IF (iflag_con.GE.3) THEN 1320 IF (iflag_coupl>=1) THEN1321 1320 CALL histdef2d(iff,clef_stations(iff), & 1322 1321 o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2") 1323 1322 CALL histdef2d(iff,clef_stations(iff), & 1324 1323 o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2") 1325 ENDIF1326 1324 ENDIF !(iflag_con.GE.3) 1327 1325 … … 1491 1489 CALL histdef2d(iff,clef_stations(iff), & 1492 1490 o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2") 1493 CALL histdef2d(iff,clef_stations(iff), &1494 o_ale%flag,o_ale%name, "ALE", "m2/s2")1495 CALL histdef2d(iff,clef_stations(iff), &1496 o_alp%flag,o_alp%name, "ALP", "W/m2")1497 CALL histdef2d(iff,clef_stations(iff),o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2")1498 CALL histdef2d(iff,clef_stations(iff),o_wape%flag,o_WAPE%name, "WAPE", "m2/s2")1499 1491 CALL histdef2d(iff,clef_stations(iff),o_wake_h%flag,o_wake_h%name, "wake_h", "-") 1500 1492 CALL histdef2d(iff,clef_stations(iff),o_wake_s%flag,o_wake_s%name, "wake_s", "-") … … 1504 1496 CALL histdef3d(iff,clef_stations(iff),o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ") 1505 1497 CALL histdef3d(iff,clef_stations(iff),o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ") 1498 CALL histdef2d(iff,clef_stations(iff),o_wape%flag,o_WAPE%name, "WAPE", "m2/s2") 1506 1499 ENDIF 1500 CALL histdef2d(iff,clef_stations(iff), & 1501 o_ale%flag,o_ale%name, "ALE", "m2/s2") 1502 CALL histdef2d(iff,clef_stations(iff), & 1503 o_alp%flag,o_alp%name, "ALP", "W/m2") 1504 CALL histdef2d(iff,clef_stations(iff),o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2") 1507 1505 CALL histdef3d(iff,clef_stations(iff),o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-") 1508 1506 CALL histdef3d(iff,clef_stations(iff),o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-") … … 1859 1857 if ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde 1860 1858 if ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then 1861 write(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref, ioget_mon_len(annee_ref,day_ref)1859 write(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len 1862 1860 timestep = ttt * dayseconde * mth_len 1863 1861 endif -
LMDZ5/branches/testing/libf/phylmd/phys_output_write.h
r1664 r1665 1 itau_w = itau_phy + itap 1 itau_w = itau_phy + itap + start_time * day_step / iphysiq 2 2 3 3 DO iff=1,nfiles … … 801 801 ! Couplage convection-couche limite 802 802 IF (iflag_con.GE.3) THEN 803 IF (iflag_coupl>=1) THEN804 803 IF (o_ale_bl%flag(iff)<=lev_files(iff)) THEN 805 804 CALL histwrite_phy(nid_files(iff),clef_stations(iff), … … 810 809 $o_alp_bl%name,itau_w,alp_bl) 811 810 ENDIF 812 ENDIF !iflag_coupl>=1813 811 ENDIF !(iflag_con.GE.3) 814 812 … … 825 823 ENDIF 826 824 827 IF (o_ale%flag(iff)<=lev_files(iff)) THEN828 CALL histwrite_phy(nid_files(iff),clef_stations(iff),829 $o_ale%name,itau_w,ale)830 ENDIF831 IF (o_alp%flag(iff)<=lev_files(iff)) THEN832 CALL histwrite_phy(nid_files(iff),clef_stations(iff),833 $o_alp%name,itau_w,alp)834 ENDIF835 IF (o_cin%flag(iff)<=lev_files(iff)) THEN836 CALL histwrite_phy(nid_files(iff),clef_stations(iff),837 $o_cin%name,itau_w,cin)838 ENDIF839 825 IF (o_wape%flag(iff)<=lev_files(iff)) THEN 840 826 CALL histwrite_phy(nid_files(iff),clef_stations(iff), … … 883 869 ENDIF ! iflag_wake>=1 884 870 871 IF (o_ale%flag(iff)<=lev_files(iff)) THEN 872 CALL histwrite_phy(nid_files(iff),clef_stations(iff), 873 $o_ale%name,itau_w,ale) 874 ENDIF 875 IF (o_alp%flag(iff)<=lev_files(iff)) THEN 876 CALL histwrite_phy(nid_files(iff),clef_stations(iff), 877 $o_alp%name,itau_w,alp) 878 ENDIF 879 IF (o_cin%flag(iff)<=lev_files(iff)) THEN 880 CALL histwrite_phy(nid_files(iff),clef_stations(iff), 881 $o_cin%name,itau_w,cin) 882 ENDIF 885 883 IF (o_Vprecip%flag(iff)<=lev_files(iff)) THEN 886 884 CALL histwrite_phy(nid_files(iff),clef_stations(iff), -
LMDZ5/branches/testing/libf/phylmd/physiq.F
r1664 r1665 614 614 REAL dd_t(klon,klev),dd_q(klon,klev) 615 615 616 real, save :: alp_bl_prescr=0. 617 real, save :: ale_bl_prescr= 0.616 real, save :: alp_bl_prescr=0.1 617 real, save :: ale_bl_prescr=4. 618 618 619 619 real, save :: ale_max=1000. … … 791 791 cIM 792 792 EXTERNAL haut2bas !variables de haut en bas 793 INTEGER lnblnk1794 EXTERNAL lnblnk1 !enleve les blancs a la fin d'une variable de type795 !caracter796 793 EXTERNAL ini_undefSTD !initialise a 0 une variable a 1 niveau de pression 797 794 EXTERNAL undefSTD !somme les valeurs definies d'1 var a 1 niveau de pression … … 1220 1217 INTEGER :: nbtr_tmp ! Number of tracer inside concvl 1221 1218 REAL, dimension(klon,klev) :: sh_in ! Specific humidity entering in phytrac 1219 integer iostat 1222 1220 1223 1221 cIM for NMC files … … 1492 1490 cCR:04.12.07: initialisations poches froides 1493 1491 c Controle de ALE et ALP pour la fermeture convective (jyg) 1494 if (iflag_wake>=1) then 1495 CALL ini_wake(0.,0.,it_wape_prescr,wape_prescr,fip_prescr 1492 CALL ini_wake(0.,0.,it_wape_prescr,wape_prescr,fip_prescr 1496 1493 s ,alp_bl_prescr, ale_bl_prescr) 1497 1494 c 11/09/06 rajout initialisation ALE et ALP du wake et PBL(YU) 1498 1495 c print*,'apres ini_wake iflag_cldcon=', iflag_cldcon 1499 endif1500 1496 1501 1497 do i = 1,klon … … 1508 1504 nCFMIP=npCFMIP 1509 1505 OPEN(98,file='npCFMIP_param.data',status='old', 1510 $ form='formatted',err=999) 1506 $ form='formatted',iostat=iostat) 1507 if (iostat == 0) then 1511 1508 READ(98,*,end=998) nCFMIP 1512 1509 998 CONTINUE … … 1540 1537 $tabijGCM, lonGCM, latGCM, iGCM, jGCM) 1541 1538 c 1542 999 CONTINUE 1539 else 1540 ALLOCATE(tabijGCM(0)) 1541 ALLOCATE(lonGCM(0), latGCM(0)) 1542 ALLOCATE(iGCM(0), jGCM(0)) 1543 end if 1543 1544 ENDIF !debut 1544 1545 … … 2041 2042 c 2042 2043 2043 CALL pbl_surface( 2044 e dtime, date0, itap, days_elapsed+1, 2045 e debut, lafin, 2046 e rlon, rlat, rugoro, rmu0, 2047 e rain_fall, snow_fall, solsw, sollw, 2048 e t_seri, q_seri, u_seri, v_seri, 2049 e pplay, paprs, pctsrf, 2050 + ftsol, falb1, falb2, u10m, v10m, 2051 s sollwdown, cdragh, cdragm, u1, v1, 2052 s albsol1, albsol2, sens, evap, 2053 s zxtsol, zxfluxlat, zt2m, qsat2m, 2054 s d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, 2055 s coefh, coefm, slab_wfbils, 2056 d qsol, zq2m, s_pblh, s_lcl, 2057 d s_capCL, s_oliqCL, s_cteiCL,s_pblT, 2058 d s_therm, s_trmb1, s_trmb2, s_trmb3, 2059 d zxrugs, zu10m, zv10m, fder, 2060 d zxqsurf, rh2m, zxfluxu, zxfluxv, 2061 d frugs, agesno, fsollw, fsolsw, 2062 d d_ts, fevap, fluxlat, t2m, 2063 d wfbils, wfbilo, fluxt, fluxu, fluxv, 2064 - dsens, devap, zxsnow, 2065 - zxfluxt, zxfluxq, q2m, fluxq, pbl_tke ) 2044 if (iflag_pbl/=0) then 2045 2046 CALL pbl_surface( 2047 e dtime, date0, itap, days_elapsed+1, 2048 e debut, lafin, 2049 e rlon, rlat, rugoro, rmu0, 2050 e rain_fall, snow_fall, solsw, sollw, 2051 e t_seri, q_seri, u_seri, v_seri, 2052 e pplay, paprs, pctsrf, 2053 + ftsol, falb1, falb2, u10m, v10m, 2054 s sollwdown, cdragh, cdragm, u1, v1, 2055 s albsol1, albsol2, sens, evap, 2056 s zxtsol, zxfluxlat, zt2m, qsat2m, 2057 s d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, 2058 s coefh, coefm, slab_wfbils, 2059 d qsol, zq2m, s_pblh, s_lcl, 2060 d s_capCL, s_oliqCL, s_cteiCL,s_pblT, 2061 d s_therm, s_trmb1, s_trmb2, s_trmb3, 2062 d zxrugs, zu10m, zv10m, fder, 2063 d zxqsurf, rh2m, zxfluxu, zxfluxv, 2064 d frugs, agesno, fsollw, fsolsw, 2065 d d_ts, fevap, fluxlat, t2m, 2066 d wfbils, wfbilo, fluxt, fluxu, fluxv, 2067 - dsens, devap, zxsnow, 2068 - zxfluxt, zxfluxq, q2m, fluxq, pbl_tke ) 2066 2069 2067 2070 2068 2071 !----------------------------------------------------------------------------------------- 2069 2072 ! ajout des tendances de la diffusion turbulente 2070 CALL add_phys_tend(d_u_vdf,d_v_vdf,d_t_vdf,d_q_vdf,dql0,'vdf')2073 CALL add_phys_tend(d_u_vdf,d_v_vdf,d_t_vdf,d_q_vdf,dql0,'vdf') 2071 2074 !----------------------------------------------------------------------------------------- 2072 2075 2073 if (mydebug) then2074 call writefield_phy('u_seri',u_seri,llm)2075 call writefield_phy('v_seri',v_seri,llm)2076 call writefield_phy('t_seri',t_seri,llm)2077 call writefield_phy('q_seri',q_seri,llm)2078 endif2079 2080 2081 IF (ip_ebil_phy.ge.2) THEN2082 ztit='after surface_main'2083 CALL diagetpq(airephy,ztit,ip_ebil_phy,2,2,dtime2076 if (mydebug) then 2077 call writefield_phy('u_seri',u_seri,llm) 2078 call writefield_phy('v_seri',v_seri,llm) 2079 call writefield_phy('t_seri',t_seri,llm) 2080 call writefield_phy('q_seri',q_seri,llm) 2081 endif 2082 2083 2084 IF (ip_ebil_phy.ge.2) THEN 2085 ztit='after surface_main' 2086 CALL diagetpq(airephy,ztit,ip_ebil_phy,2,2,dtime 2084 2087 e , t_seri,q_seri,ql_seri,qs_seri,u_seri,v_seri,paprs,pplay 2085 2088 s , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec) 2086 call diagphy(airephy,ztit,ip_ebil_phy2089 call diagphy(airephy,ztit,ip_ebil_phy 2087 2090 e , zero_v, zero_v, zero_v, zero_v, sens 2088 2091 e , evap , zero_v, zero_v, ztsol 2089 2092 e , d_h_vcol, d_qt, d_ec 2090 2093 s , fs_bound, fq_bound ) 2091 END IF 2094 END IF 2095 2096 ENDIF 2092 2097 2093 2098 c =================================================================== c … … 2239 2244 cdans le thermique sinon 2240 2245 if (iflag_coupl.eq.0) then 2241 if (debut.and.prt_level.gt.9) 2242 $ WRITE(lunout,*)'ALE et ALP imposes' 2243 do i = 1,klon 2244 con ne couple que ale 2245 c ALE(i) = max(ale_wake(i),Ale_bl(i)) 2246 ALE(i) = max(ale_wake(i),ale_bl_prescr) 2247 con ne couple que alp 2248 c ALP(i) = alp_wake(i) + Alp_bl(i) 2249 ALP(i) = alp_wake(i) + alp_bl_prescr 2250 enddo 2246 if (debut.and.prt_level.gt.9)WRITE(lunout,*) 'ALE&ALP imposes' 2247 Ale_bl(1:klon) = ale_bl_prescr 2248 Alp_bl(1:klon) = alp_bl_prescr 2251 2249 else 2252 2250 IF(prt_level>9)WRITE(lunout,*)'ALE et ALP couples au thermique' 2253 ! do i = 1,klon 2254 ! ALE(i) = max(ale_wake(i),Ale_bl(i)) 2255 ! avant ALP(i) = alp_wake(i) + Alp_bl(i) 2256 ! ALP(i) = alp_wake(i) + Alp_bl(i) + alp_offset ! modif sb 2257 ! write(20,*)'ALE',ALE(i),Ale_bl(i),ale_wake(i) 2258 ! write(21,*)'ALP',ALP(i),Alp_bl(i),alp_wake(i) 2259 ! enddo 2251 endif 2260 2252 2261 2253 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 2264 2256 ! w si <0 2265 2257 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 2258 2266 2259 do i = 1,klon 2267 2260 ALE(i) = max(ale_wake(i),Ale_bl(i)) … … 2276 2269 endif 2277 2270 enddo 2271 2278 2272 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 2279 2273 2280 endif2281 2274 do i=1,klon 2282 2275 if (alp(i)>alp_max) then … … 2634 2627 c ============== 2635 2628 2636 ! Dans le cas o ùon active les thermiques, on fait partir l'ajustement2629 ! Dans le cas o\`u on active les thermiques, on fait partir l'ajustement 2637 2630 ! a partir du sommet des thermiques. 2638 2631 ! Dans le cas contraire, on demarre au niveau 1. … … 2821 2814 ! FH 22/09/2009 2822 2815 ! La ligne ci-dessous faisait osciller le modele et donnait une solution 2823 ! as symptotique bidon et dépendant fortement du pas de temps.2816 ! asymptotique bidon et d\'ependant fortement du pas de temps. 2824 2817 ! ratqs(:,:)=sqrt(ratqs(:,:)**2+ratqss(:,:)**2) 2825 2818 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 3576 3569 3577 3570 IF (ok_hines) then 3578 3579 3571 CALL hines_gwd(klon,klev,dtime,paprs,pplay, 3580 3572 i rlat,t_seri,u_seri,v_seri, … … 3584 3576 c ajout des tendances 3585 3577 CALL add_phys_tend(d_u_hin,d_v_hin,d_t_hin,dq0,dql0,'hin') 3586 3587 3578 ENDIF 3588 c 3589 3590 c 3591 cIM cf. FLott BEG 3579 3592 3580 C STRESS NECESSAIRES: TOUTE LA PHYSIQUE 3593 3581 … … 3614 3602 cIM calcul composantes axiales du moment angulaire et couple des montagnes 3615 3603 c 3616 IF (is_sequential ) THEN3604 IF (is_sequential .and. ok_orodr) THEN 3617 3605 3618 3606 CALL aaam_bud (27,klon,klev,jD_cur-jD_ref,jH_cur, -
LMDZ5/branches/testing/libf/phylmd/phytrac.F90
r1664 r1665 214 214 SELECT CASE(type_trac) 215 215 CASE('lmdz') 216 CALL traclmdz_init(pctsrf, ftsol, tr_seri, t_seri, pplay, sh, pdtphys, aerosol, lessivage)216 CALL traclmdz_init(pctsrf, xlat, xlon, ftsol, tr_seri, t_seri, pplay, sh, pdtphys, aerosol, lessivage) 217 217 CASE('inca') 218 218 source(:,:)=0. -
LMDZ5/branches/testing/libf/phylmd/readaerosol.F90
r1492 r1665 247 247 248 248 WRITE(lunout,*) 'reading variable ',TRIM(varname),' in file ', TRIM(fname) 249 CALL check_err( nf90_open(TRIM(fname), NF90_NOWRITE, ncid) )249 CALL check_err( nf90_open(TRIM(fname), NF90_NOWRITE, ncid), "pb open "//trim(varname) ) 250 250 251 251 ! Test for equal longitudes and latitudes in file and model 252 252 !**************************************************************************************** 253 253 ! Read and test longitudes 254 CALL check_err( nf90_inq_varid(ncid, 'lon', varid) )255 CALL check_err( nf90_get_var(ncid, varid, lon_src(:)) )254 CALL check_err( nf90_inq_varid(ncid, 'lon', varid),"pb inq lon" ) 255 CALL check_err( nf90_get_var(ncid, varid, lon_src(:)),"pb get lon" ) 256 256 257 257 IF (maxval(ABS(lon_src - io_lon)) > 0.001) THEN … … 264 264 265 265 ! Read and test latitudes 266 CALL check_err( nf90_inq_varid(ncid, 'lat', varid) )267 CALL check_err( nf90_get_var(ncid, varid, lat_src(:)) )266 CALL check_err( nf90_inq_varid(ncid, 'lat', varid),"pb inq lat" ) 267 CALL check_err( nf90_get_var(ncid, varid, lat_src(:)),"pb get lat" ) 268 268 269 269 ! Invert source latitudes … … 311 311 ! 2) Find vertical dimension klev_src 312 312 !**************************************************************************************** 313 CALL check_err( nf90_inquire_dimension(ncid, dimid, len = klev_src) )313 CALL check_err( nf90_inquire_dimension(ncid, dimid, len = klev_src),"pb inq dim for PRESNIVS or lev" ) 314 314 315 315 ! Allocate variables depending on the number of vertical levels … … 330 330 !************************************************************************************************** 331 331 ierr = nf90_inq_dimid(ncid, 'TIME',dimid) 332 CALL check_err( nf90_inquire_dimension(ncid, dimid, len = nbr_tsteps) )332 CALL check_err( nf90_inquire_dimension(ncid, dimid, len = nbr_tsteps),"pb inq dim TIME" ) 333 333 ! IF (nbr_tsteps /= 12 .AND. nbr_tsteps /= 14) THEN 334 334 IF (nbr_tsteps /= 12 ) THEN … … 339 339 !**************************************************************************************** 340 340 ! Get variable id 341 CALL check_err( nf90_inq_varid(ncid, TRIM(varname), varid) )341 CALL check_err( nf90_inq_varid(ncid, TRIM(varname), varid),"pb inq var "//TRIM(varname) ) 342 342 343 343 ! Get the variable 344 CALL check_err( nf90_get_var(ncid, varid, varyear(:,:,:,:)) )344 CALL check_err( nf90_get_var(ncid, varid, varyear(:,:,:,:)),"pb get var "//TRIM(varname) ) 345 345 346 346 ! ++) Read surface pression, 12 month in one variable 347 347 !**************************************************************************************** 348 348 ! Get variable id 349 CALL check_err( nf90_inq_varid(ncid, "ps", varid) )349 CALL check_err( nf90_inq_varid(ncid, "ps", varid),"pb inq var ps" ) 350 350 ! Get the variable 351 CALL check_err( nf90_get_var(ncid, varid, psurf_glo2D) )351 CALL check_err( nf90_get_var(ncid, varid, psurf_glo2D),"pb get var ps" ) 352 352 353 353 ! ++) Read mass load, 12 month in one variable 354 354 !**************************************************************************************** 355 355 ! Get variable id 356 CALL check_err( nf90_inq_varid(ncid, "load_"//TRIM(varname), varid) )356 CALL check_err( nf90_inq_varid(ncid, "load_"//TRIM(varname), varid) ,"pb inq var load_"//TRIM(varname)) 357 357 ! Get the variable 358 CALL check_err( nf90_get_var(ncid, varid, load_glo2D) )358 CALL check_err( nf90_get_var(ncid, varid, load_glo2D),"pb get var load_"//TRIM(varname) ) 359 359 360 360 ! ++) Read ap 361 361 !**************************************************************************************** 362 362 ! Get variable id 363 CALL check_err( nf90_inq_varid(ncid, "ap", varid) )363 CALL check_err( nf90_inq_varid(ncid, "ap", varid),"pb inq var ap" ) 364 364 ! Get the variable 365 CALL check_err( nf90_get_var(ncid, varid, pt_ap) )365 CALL check_err( nf90_get_var(ncid, varid, pt_ap),"pb get var ap" ) 366 366 367 367 ! ++) Read b 368 368 !**************************************************************************************** 369 369 ! Get variable id 370 CALL check_err( nf90_inq_varid(ncid, "b", varid) )370 CALL check_err( nf90_inq_varid(ncid, "b", varid),"pb inq var b" ) 371 371 ! Get the variable 372 CALL check_err( nf90_get_var(ncid, varid, pt_b) )372 CALL check_err( nf90_get_var(ncid, varid, pt_b),"pb get var b" ) 373 373 374 374 ! ++) Read p0 : reference pressure 375 375 !**************************************************************************************** 376 376 ! Get variable id 377 CALL check_err( nf90_inq_varid(ncid, "p0", varid) )377 CALL check_err( nf90_inq_varid(ncid, "p0", varid),"pb inq var p0" ) 378 378 ! Get the variable 379 CALL check_err( nf90_get_var(ncid, varid, p0) )379 CALL check_err( nf90_get_var(ncid, varid, p0),"pb get var p0" ) 380 380 381 381 … … 412 412 413 413 ! Get variable id 414 CALL check_err( nf90_inq_varid(ncid, TRIM(cvar), varid) )414 CALL check_err( nf90_inq_varid(ncid, TRIM(cvar), varid),"pb inq var "//TRIM(cvar) ) 415 415 416 416 ! Get the variable 417 CALL check_err( nf90_get_var(ncid, varid, varmth) )417 CALL check_err( nf90_get_var(ncid, varid, varmth),"pb get var "//TRIM(cvar) ) 418 418 419 419 ! Store in variable for the whole year … … 432 432 ! 4) Close file 433 433 !**************************************************************************************** 434 CALL check_err( nf90_close(ncid) )434 CALL check_err( nf90_close(ncid),"pb in close" ) 435 435 436 436 … … 570 570 571 571 572 SUBROUTINE check_err(status )572 SUBROUTINE check_err(status,text) 573 573 USE netcdf 574 574 IMPLICIT NONE … … 576 576 INCLUDE "iniprint.h" 577 577 INTEGER, INTENT (IN) :: status 578 CHARACTER(len=*), INTENT (IN), OPTIONAL :: text 578 579 579 580 IF (status /= NF90_NOERR) THEN 580 WRITE(lunout,*) 'Error in get_aero_fromfile ',status 581 WRITE(lunout,*) 'Error in get_aero_fromfile, netcdf error code = ',status 582 IF (PRESENT(text)) THEN 583 WRITE(lunout,*) 'Error in get_aero_fromfile : ',text 584 END IF 581 585 CALL abort_gcm('get_aero_fromfile',trim(nf90_strerror(status)),1) 582 586 END IF -
LMDZ5/branches/testing/libf/phylmd/readaerosol_interp.F90
r1492 r1665 175 175 ! Reading values corresponding to the closest year taking into count the choice of aer_type. 176 176 ! For aer_type=scenario interpolation between 2 data sets is done in readaerosol. 177 ! If aer_type=mix1 or mix2, the run type and file name depends on the aerosol.177 ! If aer_type=mix1, mix2 or mix3, the run type and file name depends on the aerosol. 178 178 IF (aer_type=='preind' .OR. aer_type=='actuel' .OR. aer_type=='annuel' .OR. aer_type=='scenario') THEN 179 179 ! Standard case … … 196 196 ELSE 197 197 filename='aerosols' 198 type='preind' 199 END IF 200 ELSE IF (aer_type == 'mix3') THEN 201 ! Special case using a mix of annual sulfate file and natrual aerosols 202 IF (name_aero(id_aero) == 'SO4') THEN 203 filename='aerosols' 204 type='annuel' 205 ELSE 206 filename='aerosols' 198 207 type='preind' 199 208 END IF -
LMDZ5/branches/testing/libf/phylmd/traclmdz_mod.F90
r1454 r1665 84 84 85 85 86 SUBROUTINE traclmdz_init(pctsrf, ftsol, tr_seri, t_seri, pplay, sh, pdtphys, aerosol, lessivage)86 SUBROUTINE traclmdz_init(pctsrf, xlat, xlon, ftsol, tr_seri, t_seri, pplay, sh, pdtphys, aerosol, lessivage) 87 87 ! This subroutine allocates and initialize module variables and control variables. 88 88 ! Initialization of the tracers should be done here only for those not found in the restart file. … … 99 99 ! Input variables 100 100 REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: pctsrf ! Pourcentage de sol f(nature du sol) 101 REAL,DIMENSION(klon),INTENT(IN) :: xlat ! latitudes en degres pour chaque point 102 REAL,DIMENSION(klon),INTENT(IN) :: xlon ! longitudes en degres pour chaque point 101 103 REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: ftsol ! Temperature du sol (surf)(Kelvin) 102 104 REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT) :: tr_seri! Concentration Traceur [U/KgA] -
LMDZ5/branches/testing/libf/phylmd/wrgradsfi.F
r776 r1665 23 23 c local 24 24 25 integer lm,l ,lnblnk25 integer lm,l 26 26 27 27 -
LMDZ5/branches/testing/libf/phylmd/write_bilKP_ave.h
r776 r1665 9 9 c Champs 2D: 10 10 c 11 itau_w = itau_phy + itap 11 itau_w = itau_phy + itap + start_time * day_step / iphysiq 12 12 c 13 13 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ue_lay,zx_tmp_3d) -
LMDZ5/branches/testing/libf/phylmd/write_bilKP_ins.h
r776 r1665 7 7 ndex3d = 0 8 8 c 9 itau_w = itau_phy + itap 9 itau_w = itau_phy + itap + start_time * day_step / iphysiq 10 10 c 11 11 c Champs 3D: -
LMDZ5/branches/testing/libf/phylmd/write_histISCCP.h
r1403 r1665 9 9 ndex3d = 0 10 10 c 11 itau_w = itau_phy + itap 11 itau_w = itau_phy + itap + start_time * day_step / iphysiq 12 12 c 13 13 IF(type_run.EQ."ENSP".OR.type_run.EQ."CLIM") THEN -
LMDZ5/branches/testing/libf/phylmd/write_histREGDYN.h
r776 r1665 8 8 9 9 ndex3d = 0 10 itau_w = itau_phy + itap 10 itau_w = itau_phy + itap + start_time * day_step / iphysiq 11 11 c 12 12 CALL histwrite(nid_regdyn,"hw1",itau_w,histoW(:,:,:,1), -
LMDZ5/branches/testing/libf/phylmd/write_histdayNMC.h
r1539 r1665 5 5 c 6 6 ndex3d = 0 7 itau_w = itau_phy + itap 7 itau_w = itau_phy + itap + start_time * day_step / iphysiq 8 8 ccc 9 9 c Champs interpolles sur des niveaux de pression du NMC -
LMDZ5/branches/testing/libf/phylmd/write_histday_seri.h
r996 r1665 7 7 c 8 8 ndex2d = 0 9 itau_w = itau_phy + itap 9 itau_w = itau_phy + itap + start_time * day_step / iphysiq 10 10 c 11 11 c Champs 2D: -
LMDZ5/branches/testing/libf/phylmd/write_histhf3d.h
r776 r1665 7 7 ndex3d = 0 8 8 c 9 itau_w = itau_phy + itap 9 itau_w = itau_phy + itap + start_time * day_step / iphysiq 10 10 c 11 11 c Champs 3D: -
LMDZ5/branches/testing/libf/phylmd/write_histhfNMC.h
r1539 r1665 5 5 c 6 6 ndex3d = 0 7 itau_w = itau_phy + itap 7 itau_w = itau_phy + itap + start_time * day_step / iphysiq 8 8 ccc 9 9 c Champs interpolles sur des niveaux de pression du NMC -
LMDZ5/branches/testing/libf/phylmd/write_histmthNMC.h
r1539 r1665 5 5 c 6 6 ndex3d = 0 7 itau_w = itau_phy + itap 7 itau_w = itau_phy + itap + start_time * day_step / iphysiq 8 8 ccc 9 9 c Champs interpolles sur des niveaux de pression du NMC -
LMDZ5/branches/testing/libf/phylmd/write_histrac.h
r1664 r1665 5 5 IF (ecrit_tra > 0.) THEN 6 6 7 itau_w = itau_phy + nstep 7 itau_w = itau_phy + nstep + start_time * day_step / iphysiq 8 8 9 9 CALL histwrite_phy(nid_tra,.FALSE.,"phis",itau_w,pphis) -
LMDZ5/branches/testing/libf/phylmd/write_paramLMDZ_phy.h
r1538 r1665 27 27 c 28 28 ndex2d = 0 29 itau_w = itau_phy + itap 29 itau_w = itau_phy + itap + start_time * day_step / iphysiq 30 30 c 31 31 c Variables globales
Note: See TracChangeset
for help on using the changeset viewer.