Ignore:
Timestamp:
Jan 26, 2011, 3:37:26 AM (14 years ago)
Author:
aslmd
Message:

LMD_MM_MARS et LMD_LES_MARS convergence maintenant complete pour l'interface lmd_driver qui reconnait le cas LES avec les options de run; il y a desormais une seule version de la routine lmd_driver en commun entre MM et LES\n LMD_LES_MARS fonctionnement ameliore sans ecriture de fichiers dans modif_mars, adaptation de makeles en consequence\n LMD_LES_MARS cas test verifie\n LMD_LES_MARS ne fonctionne pas encore avec la nouvelle physique mais adaptation a priori rapide de par le travail effectue sur LMD_MM_MARS via la methode -DNEWPHYS

Location:
trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/dyn_em/solve_em.F

    r28 r34  
    863863     &        ,CST_AL=config_flags%init_AL  &
    864864     &        ,CST_TI=config_flags%init_TI  &
     865     &        ,ISFFLX=config_flags%isfflx   &
     866     &        ,DIFF_OPT=config_flags%diff_opt     &
     867     &        ,KM_OPT=config_flags%km_opt         &
    865868           ! additional diagnostics
    866869     &        ,UAVE=grid%em_uave, USTD=grid%em_ustd &
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F

    r28 r34  
    3838        CST_AL, &
    3939        CST_TI, &
     40        isfflx, &
     41        diff_opt, &
     42        km_opt, &
    4043        UAVE, USTD, &
    4144        VAVE, VSTD, &
     
    4649        SLPX,SLPY)
    4750! NB: module_lmd_driver_output1.inc : output arguments generated from Registry
     51
     52
     53
     54
    4855
    4956!==================================================================
     
    9299! Scalars
    93100INTEGER, INTENT(IN  ) :: JULDAY, itimestep, julyr,id,max_dom,MARS_MODE
     101INTEGER, INTENT(IN  ) :: isfflx,diff_opt,km_opt
    94102REAL, INTENT(IN  ) :: GMT,dt,dx,dy,RADT,CUDT
    95103REAL, INTENT(IN  ) :: CST_AL, CST_TI
     
    110118!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    111119REAL, DIMENSION( ims:ime, NUM_SOIL_LAYERS, jms:jme ), INTENT(IN   )  :: &
    112      MARS_TSOIL
     120     MARS_TSOIL 
    113121#ifdef NEWPHYS
    114122REAL, DIMENSION( ims:ime, NUM_SOIL_LAYERS, jms:jme ), INTENT(IN   )  :: &
     
    165173   ! v--- can they be modified ?
    166174   REAL,DIMENSION(:),ALLOCATABLE :: wtsurf,wco2ice,wemis
    167    REAL,DIMENSION(:,:),ALLOCATABLE :: wq2,wqsurf,wtsoil
     175   REAL,DIMENSION(:,:),ALLOCATABLE :: wq2,wqsurf,wtsoil 
    168176#ifdef NEWPHYS
    169177   REAL,DIMENSION(:,:),ALLOCATABLE :: wisoil,wdsoil
     
    220228!==================================================================
    221229
    222 flag_LES = .false.  ! "True" LES is not available in this version
     230IF (JULYR .ne. 9999) THEN
     231    flag_LES = .false.  ! "True" LES is not available in this version
     232    PRINT *, '*** REAL-CASE SIMULATION ***'
     233ELSE
     234     PRINT *, '*** IDEALIZED SIMULATION ***'
     235     IF ((diff_opt .eq. 2) .and. (km_opt .eq. 2)) THEN
     236          PRINT *, '*** type: LES ***'
     237          PRINT *, '*** diff_opt = 2 *** km_opt = 2'
     238          PRINT *, '*** forcing is isfflx = ',isfflx
     239          flag_LES = .true.
     240          !! SPECIAL LES
     241     ELSE
     242          PRINT *, '*** type: not LES ***'
     243          PRINT *, '*** diff_opt = ',diff_opt
     244          PRINT *, '*** km_opt = ',km_opt
     245          flag_LES = .false.
     246          !! IDEALIZED, no LES
     247          !! cependant, ne veut-on pas pouvoir
     248          !! prescrire un flux en idealise ??
     249     ENDIF
     250ENDIF
     251
     252
    223253print *,'** Mars ** DOMAIN',id
    224254
     
    231261jte = j_end(num_tiles)
    232262!!
    233 relax=0
    234 sponge_top=0               ! another value than 0 triggers instabilities 
    235 IF (id .gt. 1) relax=2     ! fix to avoid noise in nesting simulations ; 1 >> too much noise ...
     263IF (flag_LES .eq. .false.) THEN
     264 relax=0
     265 sponge_top=0               ! another value than 0 triggers instabilities 
     266 IF (id .gt. 1) relax=2     ! fix to avoid noise in nesting simulations ; 1 >> too much noise ...
     267ENDIF
    236268ips=its
    237269ipe=ite
    238270jps=jts
    239271jpe=jte
    240 IF (ips .eq. ids)   ips=its+relax !! IF tests necesary for parallel runs
    241 IF (ipe .eq. ide-1) ipe=ite-relax
    242 IF (jps .eq. jds)   jps=jts+relax
    243 IF (jpe .eq. jde-1) jpe=jte-relax
     272IF (flag_LES .eq. .false.) THEN
     273 IF (ips .eq. ids)   ips=its+relax !! IF tests necesary for parallel runs
     274 IF (ipe .eq. ide-1) ipe=ite-relax
     275 IF (jps .eq. jds)   jps=jts+relax
     276 IF (jpe .eq. jde-1) jpe=jte-relax
     277ENDIF
    244278kps=kts         !! start at surface
    245 kpe=kte-sponge_top
     279IF (flag_LES .eq. .false.) THEN
     280 kpe=kte-sponge_top
     281ELSE
     282 PRINT *, '*** IDEALIZED SIMULATION: LES *** kpe=kte'
     283 kpe=kte !-sponge_top
     284ENDIF
    246285
    247286!----------------------------!
     
    267306
    268307
     308PRINT *, ips, ipe, jps, jpe
     309PRINT *, ngrid
     310
     311
     312
    269313elaps = (float(itimestep)-1.)*dt  ! elapsed seconds of simulation
    270314!----------------------------------------------!
     
    287331!! put here some general information you'd like to print just once
    288332    print *, 'TILES: ', i_start,i_end, j_start, j_end  ! numbers for simple runs, arrays for parallel runs
    289     print *, 'DOMAIN: ', ide, ids, jds, jde
    290     print *, 'MEMORY: ', ime, ims, jms, jme
     333    print *, 'DOMAIN: ', ids, ide, jds, jde
     334    print *, 'MEMORY: ', ims, ime, jms, jme
    291335    print *, 'ADVECTED TRACERS: ', num_3d_s-1
    292336    print *, 'PHYSICS IS CALLED EACH...',wappel_phys
     
    328372  !
    329373  PRINT *,'** Mars ** IDEALIZED SIMULATION'
     374  PRINT *,'** Mars ** BEWARE: input_coord must be here'
    330375  open(unit=14,file='input_coord',form='formatted',status='old')
    331376  rewind(14)
     
    352397!        PRINT *,'******************   CRASH   *******************'
    353398!        PRINT *,'Irrealistic temperature...', MAXLOC(t), MINLOC(t)
     399!PRINT *, t
    354400!        PRINT *,'************************************************'
    355401!        STOP
     
    411457!        PRINT *,'OK OK OK OK'
    412458!ENDIF
     459!ENDIF
     460        !IF (          ANY(isNaN(u)) &
     461        !         .OR. ANY(isNaN(v)) &
     462        !         .OR. ANY(isNaN(t)) ) THEN
     463        ! >>> ne marche qu'avec g95
     464!print *, 'check dynamics'
     465!print *, 'u', MAXVAL(u), MINVAL(u)
     466!print *, 'v', MAXVAL(v), MINVAL(v)
     467!print *, 't', MAXVAL(t), MINVAL(t, MASK = t > 0)
     468
    413469
    414470
     
    536592!th_prof(:) = th(i,kps:kpe,j)       ! pot. temperature half level (K)
    537593
    538 
    539594!--------------------------------!
    540595! specific treatment for tracers !
     
    567622! Mass-point latitude and longitude (radians) !
    568623!---------------------------------------------!
    569 lat_val = XLAT(i,j)*DEGRAD
    570 lon_val = XLONG(i,j)*DEGRAD
     624IF (JULYR .ne. 9999) THEN
     625 lat_val = XLAT(i,j)*DEGRAD
     626 lon_val = XLONG(i,j)*DEGRAD
     627ELSE
     628 !!! IDEALIZED CASE
     629 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION lat: ',lat_input
     630 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION lon: ',lon_input
     631 lat_val = lat_input*DEGRAD
     632 lon_val = lon_input*DEGRAD
     633ENDIF
    571634
    572635!-----------------------------------------!
     
    574637! NB: usually 0 in mesoscale applications !
    575638!-----------------------------------------!
    576 zmea_val=MARS_GW(i,1,j)
    577 zstd_val=MARS_GW(i,2,j)
    578 zsig_val=MARS_GW(i,3,j)
    579 zgam_val=MARS_GW(i,4,j)
    580 zthe_val=MARS_GW(i,5,j)
     639IF (JULYR .ne. 9999) THEN
     640 zmea_val=MARS_GW(i,1,j)
     641 zstd_val=MARS_GW(i,2,j)
     642 zsig_val=MARS_GW(i,3,j)
     643 zgam_val=MARS_GW(i,4,j)
     644 zthe_val=MARS_GW(i,5,j)
     645ELSE
     646 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION GWdrag OFF'
     647 zmea_val=0.
     648 zstd_val=0.
     649 zsig_val=0.
     650 zgam_val=0.
     651 zthe_val=0.
     652ENDIF
    581653
    582654!---------------------------------!
    583655! Ground albedo & Thermal Inertia !
    584656!---------------------------------!
    585 IF (CST_AL == 0) THEN
    586 albedodat_val=MARS_ALB(i,j)
    587 ELSE
    588 albedodat_val=CST_AL
    589 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** SET CONSTANT ALBEDO ', albedodat_val
    590 ENDIF
    591 IF (CST_TI == 0) THEN
    592 inertiedat_val=MARS_TI(i,j)
    593 ELSE
    594 inertiedat_val=CST_TI
    595 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** SET CONSTANT THERMAL INERTIA ', inertiedat_val
     657IF (JULYR .ne. 9999) THEN
     658 IF (CST_AL == 0) THEN
     659 albedodat_val=MARS_ALB(i,j)
     660 ELSE
     661 albedodat_val=CST_AL
     662 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** SET CONSTANT ALBEDO ', albedodat_val
     663 ENDIF
     664 IF (CST_TI == 0) THEN
     665 inertiedat_val=MARS_TI(i,j)
     666 ELSE
     667 inertiedat_val=CST_TI
     668 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** SET CONSTANT THERMAL INERTIA ', inertiedat_val
     669 ENDIF
     670ELSE
     671 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION albedo: ', CST_AL
     672 IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION inertia: ',CST_TI
     673 albedodat_val=CST_AL
     674 inertiedat_val=CST_TI
    596675ENDIF
    597676
     
    612691! Deep soil temperatures !
    613692!------------------------!
    614 IF (MARS_TSOIL(i,1,j) .gt. 0.) THEN
    615 tsoil_val(:)=MARS_TSOIL(i,:,j)
     693IF (JULYR .ne. 9999) THEN
     694  IF (MARS_TSOIL(i,1,j) .gt. 0.) THEN
     695   tsoil_val(:)=MARS_TSOIL(i,:,j)
     696  ELSE
     697   tsoil_val = tsoil_val*0. + tsurf_val
     698  ENDIF
    616699ELSE
    617 tsoil_val = tsoil_val*0. + tsurf_val
    618 ENDIF
     700  IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION tsoil is set to tsurf'
     701  do k=1,nsoil
     702   tsoil_val(k) = tsurf_val
     703  enddo
     704ENDIF
     705
    619706#ifdef NEWPHYS
    620707isoil_val(:)=MARS_ISOIL(i,:,j)
     
    625712! Slope inclination !
    626713!-------------------!
    627 theta_val=atan(sqrt( (1000.*SLPX(i,j))**2 + (1000.*SLPY(i,j))**2 ))
    628 theta_val=theta_val/DEGRAD
     714IF (JULYR .ne. 9999) THEN
     715  theta_val=atan(sqrt( (1000.*SLPX(i,j))**2 + (1000.*SLPY(i,j))**2 ))
     716  theta_val=theta_val/DEGRAD
     717ELSE
     718  IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION slope inclination is 0'
     719  theta_val=0.
     720ENDIF
    629721
    630722!-------------------------------------------!
    631723! Slope orientation; 0 is north, 90 is east !
    632724!-------------------------------------------!
    633 psi_val=-90.*DEGRAD-atan(SLPY(i,j)/SLPX(i,j))
    634 if (SLPX(i,j) .ge. 0.) then
    635    psi_val=psi_val-180.*DEGRAD
    636 endif
    637 psi_val=360.*DEGRAD+psi_val
    638 psi_val=psi_val/DEGRAD
    639 psi_val = MODULO(psi_val+180.,360.)
     725IF (JULYR .ne. 9999) THEN
     726  psi_val=-90.*DEGRAD-atan(SLPY(i,j)/SLPX(i,j))
     727  if (SLPX(i,j) .ge. 0.) then
     728    psi_val=psi_val-180.*DEGRAD
     729  endif
     730  psi_val=360.*DEGRAD+psi_val
     731  psi_val=psi_val/DEGRAD
     732  psi_val = MODULO(psi_val+180.,360.)
     733ELSE
     734  IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION slope orientation is 0 (well, whatever)'
     735  psi_val=0.
     736ENDIF
    640737
    641738!-----------------!
     
    643740!-----------------!
    644741IF ( (i == ips) .AND. (j == jps) ) THEN
    645  PRINT *,'lat/lon ', lat_val/DEGRAD, lon_val/DEGRAD
    646  PRINT *,'emiss ', emis_val
    647  PRINT *,'phi ',phisfi_val
    648  PRINT *,'tsurf ',tsurf_val
    649  PRINT *,'aire ',aire_val
    650  PRINT *,'z_prof ',z_prof
    651  PRINT *,'dz8w_prof',dz8w_prof
    652  PRINT *,'p8w_prof ',p8w_prof
    653  PRINT *,'p_prof ',p_prof
    654  PRINT *,'t_prof ',t_prof
    655  PRINT *,'t8w_prof ',t8w_prof
    656  PRINT *,'u_prof ',u_prof
    657  PRINT *,'v_prof ',v_prof
    658  PRINT *,'tsoil ',tsoil_val
     742PRINT *,'lat/lon ', lat_val/DEGRAD, lon_val/DEGRAD
     743PRINT *,'emiss ', emis_val
     744PRINT *,'albedo ', albedodat_val
     745PRINT *,'inertie ', inertiedat_val
     746PRINT *,'phi ',phisfi_val
     747PRINT *,'tsurf ',tsurf_val
     748PRINT *,'aire ',aire_val
     749PRINT *,'z_prof ',z_prof
     750PRINT *,'dz8w_prof',dz8w_prof
     751PRINT *,'p8w_prof ',p8w_prof
     752PRINT *,'p_prof ',p_prof
     753PRINT *,'t_prof ',t_prof
     754PRINT *,'t8w_prof ',t8w_prof
     755PRINT *,'u_prof ',u_prof
     756PRINT *,'v_prof ',v_prof
     757PRINT *,'tsoil ',tsoil_val
    659758#ifdef NEWPHYS
    660  PRINT *,'isoil ',isoil_val
    661  PRINT *,'dsoil ',dsoil_val
     759PRINT *,'isoil ',isoil_val
     760PRINT *,'dsoil ',dsoil_val
    662761#endif
    663762ENDIF
     
    719818pv(subs,:) = v_prof(:)
    720819pw(subs,:) = 0   !! NB: not used in the physics, only diagnostic...
    721 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     820!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    722821!! for IDEALIZED CASES ONLY
    723822IF (JULYR .eq. 9999) pplev(subs,nlayer+1)=0.  !! pplev(subs,nlayer+1)=ptop >> NO !
    724 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     823!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     824
     825! NOTE:
     826! IF ( pplev(subs,nlayer+1) .le. 0 ) pplev(subs,nlayer+1)=ptop
     827! cree des diagnostics delirants et aleatoires dans le transfert radiatif
    725828
    726829!---------!
     
    847950#include "module_lmd_driver_output3.inc" 
    848951       !  ^-- generated from Registry
     952!TSK(i,j) = output_tab2d(subs,ind_TSURF)
    849953ENDDO
    850954ENDDO
    851955DEALLOCATE(output_tab2d)
    852956DEALLOCATE(output_tab3d)
    853 
    854957
    855958!---------------------------------------------------------------------------------!
     
    9551058DEALLOCATE(pdq)
    9561059
    957 !---------!
    958 ! display !
    959 !---------!
     1060!!---------!
     1061!! display !
     1062!!---------!
    9601063PRINT *, '** Mars ** Results from LMD physics'
    9611064PRINT *, 'u non-zero tendencies'
     
    9951098!c  Local:
    9961099      double precision xref,zx0,zteta,zz
    997 !c      xref: mean anomaly, zteta: true anomaly, zx0: eccentric anomaly
     1100!c      xref: mean anomaly, zteta: true anomaly, zx0: eccentric anomaly
    9981101      double precision year_day
    9991102      double precision peri_day,timeperi,e_elips
     
    10301133
    10311134END MODULE module_lmd_driver
     1135
Note: See TracChangeset for help on using the changeset viewer.