Ignore:
Timestamp:
Aug 30, 2013, 1:25:28 PM (11 years ago)
Author:
aslmd
Message:

LMDZ.COMMON. Added the posssibility for 3D runs without dynamics (precompiling flag NODYN). Added simple nudging (zonal wind for Saturn, but easy to extend). updated arch files for gnome with -auto. LMDZ.UNIVERSAL. Updated READMEs and latest def files (NB: saturn_tropostrato_128x96x64 and saturn_tropostrato_256x192x64 still experimental).

Location:
trunk/LMDZ.COMMON/libf
Files:
4 added
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F

    r1022 r1024  
    351351       CALL getin('dissip_pupstart',dissip_pupstart )
    352352
    353 ! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
     353! top_bound sponge: only active if iflag_top_bound!=0
    354354!                   iflag_top_bound=0 for no sponge
    355355!                   iflag_top_bound=1 for sponge over 4 topmost layers
  • trunk/LMDZ.COMMON/libf/dyn3d/gcm.F

    r1022 r1024  
    288288     &              teta,q,masse,ps,phis, time_0)
    289289        endif ! of if (planet_type.eq."mars")
    290        
     290       
     291        ! Load relaxation fields (simple nudging). AS 09/2013
     292        ! ---------------------------------------------------
     293        if (planet_type.eq."generic") then
     294         if (ok_guide) then
     295           CALL relaxetat0("relax.nc")
     296         endif
     297        endif
     298 
    291299c       write(73,*) 'ucov',ucov
    292300c       write(74,*) 'vcov',vcov
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r1022 r1024  
    2222      use cpdet_mod, only: cpdet,tpot2t,t2tpot
    2323      use sponge_mod, only: callsponge,mode_sponge,sponge
     24       use comuforc_h
     25
    2426      IMPLICIT NONE
    2527
     
    295297
    296298#ifdef CPP_IOIPSL
     299      IF (planet_type.eq."earth") THEN
    297300      if (ok_guide) then
    298301        call guide_main(itau,ucov,vcov,teta,q,masse,ps)
    299302      endif
     303      ENDIF
    300304#endif
    301305
     
    363367      endif
    364368
     369#ifdef NODYN
     370      apdiss=.false.
     371#endif
     372
    365373c-----------------------------------------------------------------------
    366374c   calcul des tendances dynamiques:
     
    376384
    377385      time = jD_cur + jH_cur
     386
     387#ifdef NODYN
     388      WRITE(lunout,*)"NO DYN !!!!!"
     389      dv(:,:) = 0.D+0
     390      du(:,:) = 0.D+0
     391      dteta(:,:) = 0.D+0
     392      dq(:,:,:) = 0.D+0
     393      dp(:) = 0.D+0
     394#else
    378395      CALL caldyn
    379396     $  ( itau,ucov,vcov,teta,ps,masse,pk,pkf,tsurpk,phis ,
    380397     $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, time )
    381398
     399      ! Simple zonal wind nudging for generic planetary model
     400      ! AS 09/2013
     401      ! ---------------------------------------------------
     402      if (planet_type.eq."generic") then
     403       if (ok_guide) then
     404         du(:,:) = du(:,:) + ((uforc(:,:)-ucov(:,:)) / facwind)
     405       endif
     406      endif
    382407
    383408c-----------------------------------------------------------------------
     
    426451            vcov=vcov+dvtidal*dt
    427452       ENDIF
     453
     454! NODYN precompiling flag
     455#endif
    428456
    429457c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
  • trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F

    r1022 r1024  
    378378       CALL getin('dissip_pupstart',dissip_pupstart )
    379379
    380 ! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
     380! top_bound sponge: only active if iflag_top_bound!=0
    381381!                   iflag_top_bound=0 for no sponge
    382382!                   iflag_top_bound=1 for sponge over 4 topmost layers
  • trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F

    r1022 r1024  
    310310     &              teta,q,masse,ps,phis, time_0)
    311311        endif ! of if (planet_type.eq."mars")
    312        
     312       
     313        ! Load relaxation fields (simple nudging). AS 09/2013
     314        ! ---------------------------------------------------
     315        if (planet_type.eq."generic") then
     316         if (ok_guide) then
     317           CALL relaxetat0("relax.nc")
     318         endif
     319        endif
     320 
    313321c       write(73,*) 'ucov',ucov
    314322c       write(74,*) 'vcov',vcov
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r1022 r1024  
    2828       use cpdet_mod, only: cpdet,tpot2t_glo_p,t2tpot_glo_p
    2929       use sponge_mod_p, only: callsponge,mode_sponge,sponge_p
     30       use comuforc_h
    3031
    3132#ifdef CPP_XIOS
     
    3334        USE wxios
    3435#endif
     36
    3537      IMPLICIT NONE
    3638
     
    315317
    316318#ifdef CPP_IOIPSL
     319      IF (planet_type.eq."earth") THEN
    317320      if (ok_guide) then
    318321!$OMP MASTER
     
    321324!$OMP BARRIER
    322325      endif
     326      ENDIF
    323327#endif
    324328
     
    437441        apdiss=.false.
    438442      endif
     443
     444#ifdef NODYN
     445      apdiss=.false.
     446#endif
     447
    439448
    440449cym    ---> Pour le moment     
     
    662671           rdaym_ini  = itau * dtvr / daysec
    663672
     673#ifdef NODYN
     674      WRITE(lunout,*)"NO DYN !!!!!"
     675      dv(:,:) = 0.D+0
     676      du(:,:) = 0.D+0
     677      dteta(:,:) = 0.D+0
     678      dq(:,:,:) = 0.D+0
     679      dp(:) = 0.D+0
     680#else
    664681! ADAPTATION GCM POUR CP(T)
    665682!      CALL caldyn_p
     
    690707cc$OMP END MASTER
    691708
     709
     710      ! Simple zonal wind nudging for generic planetary model
     711      ! AS 09/2013
     712      ! ---------------------------------------------------
     713      if (planet_type.eq."generic") then
     714       if (ok_guide) then
     715         du(:,:) = du(:,:) + ((uforc(:,:)-ucov(:,:)) / facwind)
     716       endif
     717      endif
     718
    692719c-----------------------------------------------------------------------
    693720c   calcul des tendances advection des traceurs (dont l'humidite)
     
    766793cc$OMP END MASTER
    767794
     795! NODYN precompiling flag
     796#endif
    768797
    769798c$OMP MASTER
Note: See TracChangeset for help on using the changeset viewer.