Ignore:
Timestamp:
Mar 19, 2012, 6:29:26 PM (13 years ago)
Author:
aslmd
Message:

LMDZ.GENERIC: Introduced global1d in callcorrk so that global (using sza) or local (using latitude) 1D simulations can be carried out. Converted all astronomical distances in AU instead of Mkm. This might cause problems with old start files. So added a test in iniorbit. A quite dirty test, but thatll do the job.

Location:
trunk/LMDZ.GENERIC/libf/phystd
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/callcorrk.F90

    r588 r590  
    118118
    119119      real fluxtoplanet
     120      real szangle
     121      logical global1d
     122      save szangle,global1d
    120123      real*8 taugsurf(L_NSPECTV,L_NGAUSS-1)
    121124      real*8 taugsurfi(L_NSPECTI,L_NGAUSS-1)
     
    266269         OSR_nu=0.
    267270
     271         if (ngridmx.eq.1) then
     272           PRINT*, 'Simulate global averaged conditions ?'
     273           global1d = .false. ! default value
     274           call getin("global1d",global1d)
     275           write(*,*) "global1d = ",global1d
     276           if (global1d) then
     277             PRINT *,'Solar Zenith angle (deg.) ?'
     278             PRINT *,'(assumed for averaged solar flux S/4)'
     279             szangle=60.0  ! default value
     280             call getin("szangle",szangle)
     281             write(*,*) "szangle = ",szangle
     282           endif
     283         endif
     284
    268285         firstcall=.false.   
    269286
     
    543560      endif
    544561
    545       if(ngridmx.eq.1) then       ! fixed zenith angle 'szangle' in 1D
     562      if ((ngridmx.eq.1).and.(global1d)) then       ! fixed zenith angle 'szangle' in 1D simulations w/ globally-averaged sunlight
    546563         acosz = cos(pi*szangle/180.0)
    547564         print*,'acosz=',acosz,', szangle=',szangle
    548565      else
    549          acosz=mu0(ig)          ! cosine of sun incident angle
     566         acosz=mu0(ig)          ! cosine of sun incident angle : 3D simulations or local 1D simulations using latitude
    550567      endif
    551568
     
    742759            fluxtoplanet=0.
    743760
    744             if((ngridmx.eq.1).and.(.not.(diurnal.or.tlocked)))then
     761            if((ngridmx.eq.1).and.(global1d))then
    745762               do nw=1,L_NSPECTV
    746763                  stel_fract(nw)= stel(nw) * 0.25 / acosz
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys.h

    r589 r590  
    3838     &   , rainthreshold                                                &
    3939     &   , aerofixed                                                    &
    40      &   , szangle                                                      &
    4140     &   , hydrology                                                    &
    4241     &   , sourceevol                                                   &
     
    9796      real satval
    9897      real rainthreshold
    99       real szangle
    10098      real CLFfixval
    10199      real n2mixratio
  • trunk/LMDZ.GENERIC/libf/phystd/inifis.F

    r589 r590  
    358358         write(*,*)" Fat1AU = ",Fat1AU
    359359
    360 
    361 !     1D solar zenith angle
    362          write(*,*)"Solar zenith angle in 1D?"
    363          szangle=60.0
    364          call getin("szangle",szangle)
    365          write(*,*)" szangle = ",szangle
    366360
    367361! TRACERS:
  • trunk/LMDZ.GENERIC/libf/phystd/iniorbit.F

    r253 r590  
    2626c   Input:
    2727c   ------
    28 c   apoastr       \   apoastron and periastron of the orbit
    29 c   periastr      /   in millions of kilometres.
     28c   apoastr       \   apoastron and periastron of the orbit in AU
     29c   periastr      /   
    3030c
    3131c=======================================================================
     
    5959      peri_day=pperi_day
    6060
    61       PRINT*,'Periastron in Mkm  ',periastr
    62       PRINT*,'Apoastron in Mkm  ',apoastr
     61
     62      !!!! SPARADRAP TEMPORAIRE !!!!
     63      !!!! SPARADRAP TEMPORAIRE !!!!
     64      !!!! We hope that all cases are above 25 Mkm [OK with Gliese 581d]
     65      IF ( apoastr .gt. 25.) THEN
     66        PRINT*,'!!!!! WARNING !!!!!'
     67        PRINT*,'!!!!! YOU ARE ABOUT TO WITNESS A DIRT HACK !!!!!'
     68        PRINT*,'This must be an old start file.'
     69        PRINT*,'The code changed 19/03/2012: we now use AU.'
     70        PRINT*,'So I am assuming units are in Mkm here'
     71        PRINT*,'and I am performing a conversion towards AU.'
     72        periastr = periastr / 149.598 ! Mkm to AU
     73        apoastr = apoastr / 149.598 ! Mkm to AU
     74      ENDIF
     75      !!!! SPARADRAP TEMPORAIRE !!!!
     76      !!!! SPARADRAP TEMPORAIRE !!!!
     77
     78 
     79      PRINT*,'Periastron in AU  ',periastr
     80      PRINT*,'Apoastron in AU  ',apoastr
    6381      PRINT*,'Obliquity in degrees  :',obliquit
    64       unitastr=149.597927
     82
     83
    6584      e_elips=(apoastr-periastr)/(periastr+apoastr)
    66       p_elips=0.5*(periastr+apoastr)*(1-e_elips*e_elips)/unitastr
     85      p_elips=0.5*(periastr+apoastr)*(1-e_elips*e_elips)
    6786
    6887      print*,'e_elips',e_elips
  • trunk/LMDZ.GENERIC/libf/phystd/kcm1d.F90

    r586 r590  
    137137  write(*,*) "apoastron = ",apoastr
    138138 
    139   periastr = periastr*149.598 ! AU to Mkm
    140   apoastr  = apoastr*149.598  ! AU to Mk
    141 
    142139  albedo=0.2 ! default value for albedo
    143140  print*,'Albedo of bare ground?'
  • trunk/LMDZ.GENERIC/libf/phystd/physdem1.F

    r588 r590  
    195195c Informations about Mars, only for physics
    196196      tab_cntrl(14) = year_day  ! length of year (sols) ~668.6
    197       tab_cntrl(15) = periastr  ! min. star-planet distance (Mkm) ~206.66
    198       tab_cntrl(16) = apoastr   ! max. star-planet distance (Mkm) ~249.22
     197      tab_cntrl(15) = periastr  ! min. star-planet distance (AU)
     198      tab_cntrl(16) = apoastr   ! max. star-planet distance (AU)
    199199      tab_cntrl(17) = peri_day  ! date of periastron (sols since N. spring)
    200200      tab_cntrl(18) = obliquit  ! Obliquity of the planet (deg) ~23.98
  • trunk/LMDZ.GENERIC/libf/phystd/planete.h

    r253 r590  
    55     &       obliquit,nres,                                             &
    66     &       z0,lmixmin,emin_turb,coefvis,coefir,                       &
    7      &       timeperi,e_elips,p_elips,unitastr           
     7     &       timeperi,e_elips,p_elips
    88
    99      real apoastr,periastr,year_day,peri_day,                          &
    1010     &     obliquit,nres,                                               &
    1111     &     z0,lmixmin,emin_turb,coefvis,coefir,                         &
    12      &       timeperi,e_elips,p_elips,unitastr     
     12     &       timeperi,e_elips,p_elips
    1313     
    1414
  • trunk/LMDZ.GENERIC/libf/phystd/rcm1d.F

    r589 r590  
    359359          PRINT *,"--> periastr = ",periastr
    360360      ENDIF
    361       periastr=periastr*149.598 ! AU to Mkm
    362361
    363362      apoastr = -99999.
     
    370369          PRINT *,"--> apoastr = ",apoastr
    371370      ENDIF
    372       apoastr=apoastr*149.598 ! AU to Mkm
    373371
    374372      peri_day = -99999.
  • trunk/LMDZ.GENERIC/libf/phystd/stellarlong.F

    r253 r590  
    6060c -------------------------------------------------------
    6161
    62 c   Initialisation eventuelle:
    63       if(.not.unitastr.gt.1.e-4) then
    64          call iniorbit(249.22,206.66,669.,485.,25.2)
    65       endif
    66 
    6762c  calcul de l'zanomalie moyenne
    6863
  • trunk/LMDZ.GENERIC/libf/phystd/tabfi.F

    r588 r590  
    8181
    8282
    83 c-----------------------------------------------------------------------
    84 c  Initialization of various physical constants to defaut values (nid = 0 case)
    85 c-----------------------------------------------------------------------
    86       IF (nid.eq.0) then
    87  
    88 c Reference pressure
    89 c-------------------------------------
    90 c     pressrf = 670.            ! Pression de reference (Pa) ~650
    91 
    92 c Default (Martian) parameters for the dynamics and physics
    93 c----------------------------------------------------------
    94       rad=3397200.              ! radius of Mars (m)  ~3397200 m
    95       daysec=88775.             ! length of a sol (s)  ~88775 s
    96       omeg=4.*asin(1.)/(daysec) ! rotation rate  (rad.s-1)
    97       g=3.72                    ! gravity (m.s-2) ~3.72
    98       mugaz=43.49               ! Molar mass of the atmosphere (g.mol-1) ~43.49
    99       rcp=.256793               ! = r/cp  ~0.256793
    100 
    101 c Default (Martian) parameters for physics only
    102 c----------------------------------------------
    103       year_day = 669.           ! length of year (sols) ~668.6
    104       periastr = 206.66         ! min. Star-Planet distance (Mkm) ~206.66
    105       apoastr = 249.22          ! max. Star-Planet distance (Mkm) ~249.22
    106       peri_day =  485.          ! date of periastron (sols since N. spring)
    107       obliquit = 25.19          ! Obliquity of the planet (deg) ~25.19
    108 
    109 c additional for stokes.F added by RDW
    110 c-------------------------------------
    111 !      molrad=2.2e-10   ! CO2
    112 !      visc=1.e-5       ! CO2
    113 
    114 c Boundary layer and turbulence
    115 c----------------------------
    116       z0 =  1.e-2               ! surface roughness (m) ~0.01
    117       emin_turb = 1.e-6         ! minimal energy ~1.e-8
    118       lmixmin = 30              ! mixing length ~100
    119 
    120 c Optical properties of polar caps and ground emissivity
    121 c-----------------------------------------------------
    122       emissiv=.95               ! Emissivity of martian soil ~.95
    123       emisice(1)=0.95           ! Emissivity of northern cap
    124       emisice(2)=0.95           ! Emissivity of southern cap
    125       albedice(1)=0.65          ! Albedo of northern cap
    126       albedice(2)=0.65          ! Albedo of southern cap
    127       iceradius(1) = 100.e-6    ! mean scat radius of CO2 snow (north)
    128       iceradius(2) = 100.e-6    ! mean scat radius of CO2 snow (south)
    129       dtemisice(1) = 0.4        ! time scale for snow metamorphism (north)
    130       dtemisice(2) = 0.4        ! time scale for snow metamorphism (south)
    131 
    132 c dust aerosol properties
    133 c---------------------------------
    134       tauvis= 0.2          ! mean visible optical depth
    135 
    136 c soil properties
    137       volcapa = 1.e6 ! soil volumetric heat capacity (in comsoil.h)
    138       ELSE
    13983c-----------------------------------------------------------------------
    14084c  Initialization of physical constants by reading array tab_cntrl(:)
     
    216160      p_rad=rad
    217161
    218       ENDIF    ! end of (nid = 0)
    219162
    220163c-----------------------------------------------------------------------
     
    292235      write(*,*) '(18)     obliquit : planet obliquity (deg)'
    293236      write(*,*) '(17)     peri_day : periastron date (sols since Ls=0)'
    294       write(*,*) '(15)     periastr : min. star-planet dist (Mkm)'
    295       write(*,*) '(16)     apoastr  : max. star-planet (Mkm)'
     237      write(*,*) '(15)     periastr : min. star-planet dist (UA)'
     238      write(*,*) '(16)     apoastr  : max. star-planet (UA)'
    296239      write(*,*) '(14)     year_day : length of year (in sols)'
    297240      write(*,*) '(5) rad : radius of the planet (m)'
Note: See TracChangeset for help on using the changeset viewer.