Changeset 4191


Ignore:
Timestamp:
Dec 20, 2019, 12:41:10 AM (5 years ago)
Author:
dubos
Message:

simple_physics : cleanup astronomy

Location:
dynamico_lmdz/simple_physics/phyparam
Files:
1 deleted
4 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/simple_physics/phyparam/param/iniphyparam.F

    r4190 r4191  
    6464      INTEGER ig,ierr,offset
    6565 
    66       EXTERNAL inifrict,iniorbit,orbite
     66      EXTERNAL inifrict,orbite
    6767 
    6868      print*,'INIPHYPARAM'
  • dynamico_lmdz/simple_physics/phyparam/param/phyparam.F

    r4190 r4191  
    253253         print*,tsoil(ngrid/2+1,nsoilmx/2+2)
    254254         print*,'TS ',tsurf(igout),tsoil(igout,5)
    255          CALL iniorbit(aphelie,periheli,year_day,peri_day,obliquit)
     255         CALL iniorbit
    256256
    257257         if (.not.callrad) then
  • dynamico_lmdz/simple_physics/phyparam/param/zenang.F

    r4176 r4191  
    11      SUBROUTINE zenang(klon,longi,gmtime,pdtrad,lat,long,
    22     s                  pmu0,frac)
     3      USE astronomy
    34      IMPLICIT none
    45c=============================================================
     
    2425c frac-----OUTPUT: ensoleillement moyen entre gmtime et gmtime+pdtrad
    2526c================================================================
    26 #include "comorbit.h"
    2727      integer klon
    2828c================================================================
     
    155155      END
    156156c===================================================================
    157 #ifdef PASLA
    158       SUBROUTINE zenith (klon,longi, gmtime, lat, long,
    159      s                   pmu0, fract)
    160       IMPLICIT none
    161 c
    162 c Auteur(s): Z.X. Li (LMD/ENS)
    163 c
    164 c Objet: calculer le cosinus de l'angle zenithal du soleil en
    165 c        connaissant la declinaison du soleil, la latitude et la
    166 c        longitude du point sur la terre, et le temps universel
    167 c
    168 c Arguments d'entree:
    169 c     longi  : declinaison du soleil (en degres)
    170 c     gmtime : temps universel en second qui varie entre 0 et 86400
    171 c     lat    : latitude en degres
    172 c     long   : longitude en degres
    173 c Arguments de sortie:
    174 c     pmu0   : cosinus de l'angle zenithal
    175 c
    176 c====================================================================
    177 #include "YOMCST.h"
    178 c====================================================================
    179       INTETER klon
    180       REAL longi, gmtime
    181       REAL lat(klon), long(klon), pmu0(klon), fract(klon)
    182 c=====================================================================
    183       INTEGER n
    184       REAL zpi, zpir, omega, zgmtime
    185       REAL incl, lat_sun, lon_sun
    186 c----------------------------------------------------------------------
    187       zpi = 4.0*ATAN(1.0)
    188       zpir = zpi / 180.0
    189       zgmtime=gmtime*86400.
    190 c
    191       incl=R_incl * zpir
    192 c
    193       lon_sun = longi * zpir
    194       lat_sun = ASIN (SIN(lon_sun)*SIN(incl) )
    195 c
    196 c--initialisation a la nuit
    197 c
    198       DO n =1, klon
    199         pmu0(n)=0.
    200         fract(n)=0.0
    201       ENDDO
    202 c
    203 c 1 degre en longitude = 240 secondes en temps
    204 c
    205       DO n = 1, klon
    206          omega = zgmtime + long(n)*86400.0/360.0
    207          omega = omega / 86400.0 * 2.0 * zpi
    208          omega = MOD(omega + 2.0 * zpi, 2.0 * zpi)
    209          omega = omega - zpi
    210          pmu0(n) = sin(lat(n)*zpir) * sin(lat_sun)
    211      .           + cos(lat(n)*zpir) * cos(lat_sun)
    212      .           * cos(omega)
    213          pmu0(n) = MAX (pmu0(n), 0.0)
    214          IF (pmu0(n).GT.1.E-6) fract(n)=1.0
    215       ENDDO
    216 c
    217       RETURN
    218       END
    219 #endif
  • dynamico_lmdz/simple_physics/phyparam/physics/astronomy.F90

    r4190 r4191  
    8585  END SUBROUTINE solarlong
    8686 
     87  SUBROUTINE iniorbit
     88    !=======================================================================
     89    !
     90    !   Auteur:
     91    !   -------
     92    !     Frederic Hourdin      22 Fevrier 1991
     93    !
     94    !   Objet:
     95    !   ------
     96    !    Initialisation du sous programme orbite qui calcule
     97    !    a une date donnee de l'annee de duree year_day commencant
     98    !    a l'equinoxe de printemps et dont le perihelie se situe
     99    !    a la date peri_day, la distance au soleil et la declinaison.
     100    !
     101    !   Interface:
     102    !   ----------
     103    !   - initialise certaines variables de ce module
     104    !   - Doit etre appele avant d'utiliser orbite.
     105    !
     106    !   Arguments:
     107    !   ----------
     108    !
     109    !   Input:
     110    !   ------
     111    !   aphelie       \   aphelie et perihelie de l'orbite
     112    !   periheli      /   en millions de kilometres.
     113    !
     114    !=======================================================================
     115   
     116    !-----------------------------------------------------------------------
     117   
     118    !   Local:
     119    !   ------
     120    REAL zxref,zanom,zz,zx0,zdx
     121    INTEGER iter
     122   
     123    !-----------------------------------------------------------------------
     124   
     125    PRINT*,'Perihelie en Mkm  ',periheli
     126    PRINT*,'Aphelise  en Mkm  ',aphelie
     127    PRINT*,'obliquite en degres  :',obliquit
     128   
     129    e_elips=(aphelie-periheli)/(periheli+aphelie)
     130    p_elips=0.5*(periheli+aphelie)*(1-e_elips*e_elips)/unitastr
     131   
     132    print*,'e_elips',e_elips
     133    print*,'p_elips',p_elips
     134   
     135    !-----------------------------------------------------------------------
     136    ! calcul de l'angle polaire et de la distance au soleil :
     137    ! -------------------------------------------------------
     138   
     139    !  calcul de l'zanomalie moyenne
     140   
     141    zz=(year_day-peri_day)/year_day
     142    zanom=2.*pi*(zz-nint(zz))
     143    zxref=abs(zanom)
     144    PRINT*,'zanom  ',zanom
     145   
     146    !  resolution de l'equation horaire  zx0 - e * sin (zx0) = zxref
     147    !  methode de Newton
     148   
     149    zx0=zxref+e_elips*sin(zxref)
     150    DO  iter=1,100
     151       zdx=-(zx0-e_elips*sin(zx0)-zxref)/(1.-e_elips*cos(zx0))
     152!       if(abs(zdx).le.(1.e-12)) goto 120
     153       zx0=zx0+zdx
     154    END DO
     155   
     156    zx0=zx0+zdx
     157    if(zanom.lt.0.) zx0=-zx0
     158    PRINT*,'zx0   ',zx0
     159   
     160    ! zteta est la longitude solaire
     161   
     162    timeperi=2.*atan(sqrt((1.+e_elips)/(1.-e_elips))*tan(zx0/2.))
     163    PRINT*,'longitude solaire du perihelie timeperi = ',timeperi
     164   
     165   
     166  END SUBROUTINE iniorbit
     167
    87168END MODULE astronomy
     169
Note: See TracChangeset for help on using the changeset viewer.