Class rad_short_income
In: radiation/rad_short_income.f90

�­æ³¢�¥å� (å¤��½å�¥å�)

Short wave (insolation) incoming

Note that Japanese and English are described in parallel.

�­æ³¢�¥å� (å¤��½å�¥å�) ��è¨�ç®����¾ã��.

Calculate short wave (insolation) incoming radiation.

Procedures List

ShortIncoming :�­æ³¢�¥å� (å¤��½å�¥å�) ���ç®�
———— :————
ShortIncoming :Calculate short wave (insolation) incoming radiation.

NAMELIST

NAMELIST#rad_short_income_nml

Methods

Included Modules

dc_types dc_message constants0 gridset timeset axesset dc_calendar gtool_historyauto dc_iounit namelist_util

Public Instance methods

Subroutine :
xy_InAngle(0:imax-1, 1:jmax) :real(DP), intent(out), optional
: sec ( �¥å�è§� ). sec ( Incident angle )
DistFromStarScld :real(DP), intent(out), optional
: è»����·å��å¾��§ã�¹ã�±ã�¼ã���³ã�°ã����������������� Distance from the star scaled by semimajor axis of the planet‘s orbit
xy_CosZet(0:imax-1, 1:jmax) :real(DP), intent(out), optional
: cos( �¥å�è§� ) cos( Incident angle )
DiurnalMeanFactor :real(DP), intent(out), optional
PlanetLonFromVE :real(DP), intent(out), optional
: 中å�����中å�������座æ����������¥å���¹ã����æ¸��£ã���������åº� Longitude of the planet measured from the vernal equinox in the coordinate that the central star is located on the origin.
FlagOutput :logical , intent(in ), optional

�­æ³¢�¥å� (å¤��½å�¥å�) ��è¨�ç®����¾ã��.

Calculate short wave (insolation) incoming radiation.

[Source]

  subroutine RadShortIncome( xy_InAngle, DistFromStarScld, xy_CosZet, DiurnalMeanFactor, PlanetLonFromVE, FlagOutput )
    !
    ! �­æ³¢�¥å� (å¤��½å�¥å�) ��è¨�ç®����¾ã��.
    !
    ! Calculate short wave (insolation) incoming radiation. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! �¥ä������³æ���»ã������±ã��
    ! Date and time handler
    !
    use dc_calendar, only: DCCalInquire, DCCalDateEvalSecOfDay

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut


    ! 宣�� ; Declaration statements
    !
    implicit none
    real(DP), intent(out), optional :: xy_InAngle (0:imax-1, 1:jmax)
                              ! sec ( �¥å�è§� ). 
                              ! sec ( Incident angle )
    real(DP), intent(out), optional :: DistFromStarScld
                              ! è»����·å��å¾��§ã�¹ã�±ã�¼ã���³ã�°ã�����������������
                              ! Distance from the star scaled
                              ! by semimajor axis of the planet's orbit
    real(DP), intent(out), optional :: xy_CosZet(0:imax-1, 1:jmax)
                              ! cos( �¥å�è§� )
                              ! cos( Incident angle )
    real(DP), intent(out), optional :: DiurnalMeanFactor
    real(DP), intent(out), optional :: PlanetLonFromVE
                              ! 中å�����中å�������座æ����������¥å���¹ã����æ¸��£ã���������åº�
                              ! Longitude of the planet measured from the vernal equinox
                              ! in the coordinate that the central star is located on 
                              ! the origin.
    logical , intent(in ), optional :: FlagOutput


    ! �業��
    ! Work variables
    !
    integer:: i                ! çµ�åº��¹å�������� DO ���¼ã�����業å���
                               ! Work variables for DO loop in longitude
    integer:: j                ! ç·�º¦�¹å�������� DO ���¼ã�����業å���
                               ! Work variables for DO loop in latitude
    real(DP):: SinDel          ! 赤緯
                               ! Declination
    real(DP):: CosZet          ! �¥å�è§�
                               ! Incidence angle
    real(DP):: AngleMaxLon     ! �¥å�����大ã������ç·�º¦

    real(DP):: HourAngle       ! ���
                               ! Hour angle
    real(DP):: ClockByDay      ! ���»ã���¥ã�§è¡¨è¨��������� (0.0 - 1.0)
                               ! Clock expressed by day (0.0 - 1.0)


    real(DP) :: xy_InAngleLV       (0:imax-1, 1:jmax)
                               ! sec ( �¥å�è§� ). 
                               ! sec ( Incident angle )
                               ! (local variable)
    real(DP) :: DistFromStarScldLV
                               ! Distance between the central star and the planet
                               ! (local variable)
    real(DP) :: xy_CosZetLV        (0:imax-1, 1:jmax)
                               ! cos( �¥å�è§� )
                               ! cos( Incident angle )
                               ! (local variable)
    real(DP) :: PlanetLonFromVELV

    integer         :: hour_in_a_day, min_in_a_hour
    real(DP)        :: sec_in_a_min, sec_in_a_day


    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. rad_short_income_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    ! Set flag for diurnally averaged insolation : This is temporary one.
    !
    if ( present( DiurnalMeanFactor ) ) then
      if ( ( .not. FlagAnnualMean ) .and. FlagDiurnalMean ) then
        DiurnalMeanFactor = 1.0_DP / PI
      else
        DiurnalMeanFactor = 1.0_DP
      end if
    end if


    ! ������転���������
    ! Flag for synchronous rotation
    if ( .not. FlagRadSynchronous ) then

      ! å¹�, �¥å¹³���¥å����ç®�
      ! Calculate annual mean, daily mean insolation
      !

      if ( FlagAnnualMean .and. FlagDiurnalMean ) then

        do i = 0, imax - 1
          do j = 1, jmax
            xy_CosZetLV(i,j) = IncomAIns + IncomBIns * cos( y_Lat(j) )**2

            if ( xy_CosZetLV(i,j) > 0.0_DP ) then
              xy_InAngleLV(i,j) = 1.0_DP / xy_CosZetLV(i,j)
            else
              xy_InAngleLV(i,j) = 0.
            end if

          end do
        end do

        DistFromStarScldLV = 1.0_DP
        SinDel             = 0.0_DP
        PlanetLonFromVELV  = 0.0_DP

      else if ( .not. FlagAnnualMean ) then

        ! Set sine of declination and distance between a planet and a central star 
        ! scaled with semi-major axis
        !
        if ( FlagPerpetual ) then
          SinDel             = PerpSinDel
          DistFromStarScldLV = PerpDistFromStarScld
        else
          call ShortIncomCalcOrbParam( SinDel, DistFromStarScldLV, PlanetLonFromVELV )
          if ( present( PlanetLonFromVE ) ) PlanetLonFromVE = PlanetLonFromVELV
        end if


        call DCCalInquire( hour_in_day      = hour_in_a_day, min_in_hour      = min_in_a_hour, sec_in_min       = sec_in_a_min )
        sec_in_a_day  = hour_in_a_day * min_in_a_hour * sec_in_a_min


        if ( FlagSpecifySolDay ) then
          ! case with solar day which is different from sec_in_a_day (rotation
          ! period)
          ClockByDay = mod( TimeN / SolDay, 1.0_DP )
        else
          ! case with solar day which is the same as sec_in_a_day (rotation
          ! period)
          ClockByDay = DCCalDateEvalSecOfDay( TimeN, date = InitialDate )
          ClockByDay = ClockByDay / sec_in_a_day
        end if


!!$        write( 6, * ) '###', TimeN, ClockByDay, mod( TimeN / sec_in_a_day, 1.0_DP )
!!$        write( 60, * ) TimeN, ClockByDay, mod( TimeN / sec_in_a_day, 1.0_DP )
!!$        call flush( 60 )


        do i = 0, imax - 1
          do j = 1, jmax


            if ( FlagDiurnalMean ) then
              HourAngle = 0.0_DP
            else
              HourAngle = ClockByDay * 2.0_DP * PI - PI + x_Lon(i)
            end if

            CosZet = sin( y_Lat(j) ) * SinDel + cos( y_Lat(j) ) * sqrt( 1.0_DP - SinDel**2 ) * cos( HourAngle )

            xy_CosZetLV(i,j) = CosZet

            if ( CosZet > 0.0_DP ) then
              xy_InAngleLV(i,j)       = 1.0_DP / CosZet
            else
              xy_InAngleLV(i,j)       = 0.
            end if

          end do
        end do

      else

        ! 対å������������¥å��¿ã�¤ã��
        ! not implemented insolation type
        !
        call MessageNotify( 'E', module_name, 'This type of insolation is not impremented' )

      end if

    else

      ! �­æ³¢�¥å� (å¤��½å�¥å�) ��è¨�ç®����¾ã��.
      ! ������転æ�������³å���������,
      ! 常ã���åº� 90 åº��§æ��大å�¥å�, çµ�åº� 180-360 åº��§å�¥å��¼ã�­ã�����£ã�����¾ã��.
      !
      ! Calculate short wave (insolation) incoming radiation.
      ! A planet with synchronized rotation are assumed.
      ! Incoming is max at latitude 90 deg., and zero between 180 and 360 deg. constantly.
      do i = 0, imax - 1
         AngleMaxLon  = - PI / 2.0_DP + x_Lon( i )
         do j = 1, jmax
            CosZet = cos( y_Lat(j) ) * cos( AngleMaxLon )

            xy_CosZetLV(i,j) = CosZet

            if ( CosZet > 0.0_DP ) then
               xy_InAngleLV(i,j) = 1.0_DP / CosZet
            else
               xy_InAngleLV(i,j) = 0.0_DP
            end if

            DistFromStarScldLV = 1.0_DP
         end do
      end do

    end if


    if ( present( xy_InAngle ) ) then
      xy_InAngle = xy_InAngleLV
    end if
    if ( present( xy_CosZet ) ) then
      xy_CosZet = xy_CosZetLV
    end if
    if ( present( DistFromStarScld ) ) then
      DistFromStarScld = DistFromStarScldLV
    end if

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    if ( present( FlagOutput ) ) then
      if ( FlagOutput ) then
        call HistoryAutoPut( TimeN, 'Decl'            , asin(SinDel)*180.0_DP/PI      )
        call HistoryAutoPut( TimeN, 'DistFromStarScld', DistFromStarScldLV            )
        call HistoryAutoPut( TimeN, 'PlanetLonFromVE' , PlanetLonFromVELV*180.0_DP/PI )
      end if
    else
      call HistoryAutoPut( TimeN, 'Decl'            , asin(SinDel)*180.0_DP/PI      )
      call HistoryAutoPut( TimeN, 'DistFromStarScld', DistFromStarScldLV            )
      call HistoryAutoPut( TimeN, 'PlanetLonFromVE' , PlanetLonFromVELV*180.0_DP/PI )
    end if


  end subroutine RadShortIncome
Subroutine :

rad_short_income �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. NAMELIST#rad_short_income_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��.

"rad_short_income" module is initialized. "NAMELIST#rad_short_income_nml" is loaded in this procedure.

This procedure input/output NAMELIST#rad_short_income_nml .

[Source]

  subroutine RadShortIncomeInit
    !
    ! rad_short_income �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. 
    ! NAMELIST#rad_short_income_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��. 
    !
    ! "rad_short_income" module is initialized. 
    ! "NAMELIST#rad_short_income_nml" is loaded in this procedure. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ç¨��¥å�������¡ã��
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! æ¨�æº��ºå�����ç½����. Unit number of standard output

    ! ���¡ã�¤ã���¥å�ºå��è£���
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoAddVariable

    ! �����¥æ��������±ã��
    ! Calendar and Date handler
    !
    use dc_calendar, only: DC_CAL_DATE, DCCalDateInquire, DCCalDateCreate, DCCalDateDifference, DCCalConvertByUnit

    ! NAMELIST ���¡ã�¤ã���¥å�����¢ã�������¼ã���£ã������
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid

    ! 宣�� ; Declaration statements
    !
    implicit none

    integer:: EpochYear, EpochMonth, EpochDay, EpochHour, EpochMin
                              ! �����¥æ�� (å¹´æ���¥æ����).
                              ! "TimeAtEpoch" ��è²����´å�������¡ã����使ç��������.
                              !
                              ! Date at epoch (year, month, day, hour, minute)
                              ! These are used when "TimeAtEpoch" is negative.
    real(DP):: EpochSec
                              ! �����¥æ�� (ç§�).
                              ! "TimeAtEpoch" ��è²����´å�������¡ã����使ç��������.
                              !
                              ! Date at epoch (second)
                              ! These are used when "TimeAtEpoch" is negative.

    type(DC_CAL_DATE):: EpochDate
                              ! �������¥æ��
                              ! Date at epoch

    real(DP)         :: PerpDelDeg
                              ! Declination angle in degree used for perpetual experiment

    real(DP)         :: SolDayValue
    character(TOKEN) :: SolDayUnit

    integer:: unit_nml        ! NAMELIST ���¡ã�¤ã�����¼ã���³ç���ç½����. 
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 読ã�¿è¾¼�¿æ���� IOSTAT. 
                              ! IOSTAT of NAMELIST read

    logical         :: FlagUseOfEpochDate
    character(TOKEN):: date_print


    ! NAMELIST å¤��°ç¾¤
    ! NAMELIST group name
    !
    namelist /rad_short_income_nml/ FlagRadSynchronous, FlagAnnualMean, FlagDiurnalMean, FlagPerpetual, PerpDelDeg, PerpDistFromStarScld, EpsOrb, PerLonFromVE, LonFromVEAtEpoch, Eccentricity, TimeAtEpoch, EpochYear, EpochMonth, EpochDay, EpochHour, EpochMin, EpochSec, MaxItrEccAnomaly, ThreEccAnomalyError, IncomAIns, IncomBIns, IncomAZet, IncomBZet, FlagSpecifySolDay, SolDayValue, SolDayUnit
          !
          ! �����������¤ã���¤ã��������������ç¶� "rad_short_income#RadShortIncomeInit" 
          ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������. 
          !
          ! Refer to source codes in the initialization procedure
          ! "rad_short_income#RadShortIncomeInit" for the default values. 
          !

    ! ���� ; Executable statement
    !

    if ( rad_short_income_inited ) return


    ! �����������¤ã��¨­å®�
    ! Default values settings
    !
    FlagRadSynchronous       = .false.
    FlagAnnualMean           = .true.
    FlagDiurnalMean          = .true.
    FlagPerpetual            = .false.

    !---

    PerpDelDeg               = 0.0_DP
    PerpDistFromStarScld     = 1.0_DP

    !---

    EpsOrb               =   23.5_DP    ! Earth-like value
    PerLonFromVE         =    0.0_DP
    LonFromVEAtEpoch     =  280.0_DP    ! This value results in the fact that the planet
                                        ! is located at the position of vernal equinox 
                                        ! at 80 days after calculation with the use of 
                                        ! "360day" calendar.
    Eccentricity         =    0.0_DP
    TimeAtEpoch          =    0.0_DP
    EpochYear            =   -1
    EpochMonth           =   -1
    EpochDay             =   -1
    EpochHour            =   -1
    EpochMin             =   -1
    EpochSec             =   -1.0_DP

    !---

    ! Sample values for the Earth
    !  References: 
    !    Duffett-Smith, P., Practical astronomy with your calculator Third Edition, 
    !    Cambridge University Press, pp.185, 1988.
    !
!!$    EpsOrb               =   23.44_DP                ! Rika nenpyo (Chronological 
!!$                                                     ! Scientific Tables 2010)
!!$    PerLonFromVE         =  102.768413_DP + 180.0_DP ! Duffett-Smith (1988), p.105
!!$                                                     ! modified (plus 180 degrees)
!!$    LonFromVEAtEpoch     =   99.403308_DP + 180.0_DP ! Duffett-Smith (1988), p.105
!!$                                                     ! modified (plus 180 degrees)
!!$    Eccentricity         =    0.016713_DP            ! Duffett-Smith (1988), p.105
!!$    TimeAtEpoch          =   -1.0_DP                 ! EpochXXX written below are used 
!!$                                                     ! because this is negative.
!!$    EpochYear            = 1990                      ! Duffett-Smith (1988), p.105
!!$    EpochMonth           =    1
!!$    EpochDay             =    1
!!$    EpochHour            =    0
!!$    EpochMin             =    0
!!$    EpochSec             =    0.0_DP
    !---

    ! Sample values for Mars
    !  References: 
    !    Allison, M., Geophys. Res. Lett., 24, 1967-1970, 1997.
    !
!!$    EpsOrb               =   25.19_DP              ! Allison (1997)
!!$    PerLonFromVE         =  250.98_DP              ! Allison (1997) (modified)
!!$    LonFromVEAtEpoch     =  -10.342_DP             ! Arbitrarily set for clarity
!!$                                                   ! This results in Ls ~ 0 at Time = 0
!!$    Eccentricity         =    0.0934_DP            ! Allison (1997), value at epoch J2000
!!$    TimeAtEpoch          =    0.0_DP               ! Arbitrarily set for clarity
!!$    EpochYear            =   -1                    ! not used
!!$    EpochMonth           =   -1
!!$    EpochDay             =   -1
!!$    EpochHour            =   -1
!!$    EpochMin             =   -1
!!$    EpochSec             =   -1.0_DP

    !---

    MaxItrEccAnomaly     = 20
    ThreEccAnomalyError  = 1e-6_DP

    IncomAIns            = 0.127_DP   ! see dcpam document for reference
    IncomBIns            = 0.183_DP   ! see dcpam document for reference
    IncomAZet            = 0.410_DP   ! see dcpam document for reference
    IncomBZet            = 0.590_DP   ! see dcpam document for reference

    FlagSpecifySolDay = .false.
    SolDayValue       = 0.0_DP
    SolDayUnit        = 'sec'


    ! NAMELIST ����¿è¾¼��
    ! NAMELIST is input
    !
    if ( trim(namelist_filename) /= '' ) then
      call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in)

      rewind( unit_nml )
      read( unit_nml, nml = rad_short_income_nml, iostat = iostat_nml )        ! (out)
      close( unit_nml )

      call NmlutilMsg( iostat_nml, module_name ) ! (in)
    end if


    PerpSinDel = sin( PerpDelDeg * PI / 180.0_DP )


    FlagUseOfEpochDate = .false.

    if ( TimeAtEpoch < 0.0_DP ) then
      call DCCalDateCreate( year  = EpochYear, month = EpochMonth, day   = EpochDay, hour  = EpochHour, min   = EpochMin, sec   = EpochSec, date  = EpochDate )    ! (out) optional

      TimeAtEpoch = DCCalDateDifference( start_date = InitialDate, end_date   = EpochDate )

      FlagUseOfEpochDate = .true.
    end if

    SolDay = DCCalConvertByUnit( SolDayValue, SolDayUnit, 'sec' )

    ! ä¿�å­�������°ã���²ã��ä»���
    ! Allocate variables for saving
    !

    ! ���¹ã�������¼ã�¿å�ºå�����������¸ã����°ç�»é��
    ! Register of variables for history data output
    !
!!$    call HistoryAutoAddVariable( 'xxxxx' , &
!!$      & (/ 'lon ', 'lat ', 'sig', 'time'/), &
!!$      & 'xxxx', 'W m-2' )

    call HistoryAutoAddVariable( 'ISR' , (/ 'lon ', 'lat ', 'time'/), 'incoming shortwave', 'W m-2' )

    call HistoryAutoAddVariable( 'Decl' , (/ 'time'/), 'declination angle', 'degree' )

    call HistoryAutoAddVariable( 'DistFromStarScld' , (/ 'time'/), 'distance between the central star and the planet', '1' )

    call HistoryAutoAddVariable( 'PlanetLonFromVE' , (/ 'time'/), 'planetary longitude from the vernal equinox', 'degree' )

    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'ShortIncomming:' )
    call MessageNotify( 'M', module_name, '  FlagRadSynchronous       = %b', l = (/ FlagRadSynchronous /) )
    call MessageNotify( 'M', module_name, '  FlagAnnualMean           = %b', l = (/ FlagAnnualMean            /) )
    call MessageNotify( 'M', module_name, '  FlagDiurnalMean          = %b', l = (/ FlagDiurnalMean           /) )
    call MessageNotify( 'M', module_name, '  FlagPerpetual            = %b', l = (/ FlagPerpetual             /) )
    call MessageNotify( 'M', module_name, '  PerpDelDeg               = %f', d = (/ PerpDelDeg                /) )
    call MessageNotify( 'M', module_name, '  PerpDistFromStarScld     = %f', d = (/ PerpDistFromStarScld      /) )
    call MessageNotify( 'M', module_name, '  EpsOrb                   = %f', d = (/ EpsOrb                   /) )
    call MessageNotify( 'M', module_name, '  PerLonFromVE             = %f', d = (/ PerLonFromVE             /) )
    call MessageNotify( 'M', module_name, '  Eccentricity             = %f', d = (/ Eccentricity             /) )

    if ( FlagUseOfEpochDate ) then
      call DCCalDateInquire( date_print, date = EpochDate )
      call MessageNotify( 'M', module_name, '  EpochDate  = %c', c1 = trim(date_print) )
    end if
    call MessageNotify( 'M', module_name, '  TimeAtEpoch              = %f', d = (/ TimeAtEpoch              /) )
    call MessageNotify( 'M', module_name, '  LonFromVEAtEpoch         = %f', d = (/ LonFromVEAtEpoch         /) )

    call MessageNotify( 'M', module_name, '  MaxItrEccAnomaly         = %d', i = (/ MaxItrEccAnomaly         /) )
    call MessageNotify( 'M', module_name, '  ThreEccAnomalyError      = %f', d = (/ ThreEccAnomalyError      /) )
    call MessageNotify( 'M', module_name, '  IncomAIns                = %f', d = (/ IncomAIns                /) )
    call MessageNotify( 'M', module_name, '  IncomBIns                = %f', d = (/ IncomBIns                /) )
    call MessageNotify( 'M', module_name, '  IncomAZet                = %f', d = (/ IncomAZet                /) )
    call MessageNotify( 'M', module_name, '  IncomBZet                = %f', d = (/ IncomBZet                /) )

    call MessageNotify( 'M', module_name, '  FlagSpecifySolDay        = %b', l = (/ FlagSpecifySolDay        /) )
    call MessageNotify( 'M', module_name, '  SolDay                   = %f', d = (/ SolDay                   /) )


    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    rad_short_income_inited = .true.

  end subroutine RadShortIncomeInit

Private Instance methods

Eccentricity
Variable :
Eccentricity :real(DP), save
: �¢å���. Eccentricity.
EpsOrb
Variable :
EpsOrb :real(DP), save
: 赤é���¾æ��è§�. Inclination of equator to orbit.
FlagAnnualMean
Variable :
FlagAnnualMean :logical, save
: å¹´å¹³���¥å�������. Flag for annual mean incoming radiation.
FlagDiurnalMean
Variable :
FlagDiurnalMean :logical, save
: �¥å¹³���¥å�������. Flag for diurnal mean incoming radiation.
FlagPerpetual
Variable :
FlagPerpetual :logical, save
: å­£ç�å¤��������¥å�������. Flag for perpetual incoming radiation.
FlagRadSynchronous
Variable :
FlagRadSynchronous :logical
: ������転��������� Flag for synchronous rotation
FlagSpecifySolDay
Variable :
FlagSpecifySolDay :logical, save
: Flag for specifying solar day
IncomAIns
Variable :
IncomAIns :real(DP), save
: $ A_{ins} $ . å¹´å¹³���¥å������. Coefficient of annual mean incoming radiation.
IncomAZet
Variable :
IncomAZet :real(DP), save
: $ A_{zeta} $ . å¹´å¹³���¥å�è§������. AIns ������. Coefficient of annual mean incoming radiation. Same as "AIns".
IncomBIns
Variable :
IncomBIns :real(DP), save
: $ B_{ins} $ . å¹´å¹³���¥å������. AIns ������. Coefficient of annual mean incoming radiation. Same as "AIns".
IncomBZet
Variable :
IncomBZet :real(DP), save
: $ B_{zeta} $ . å¹´å¹³���¥å�è§������. AIns ������. Coefficient of annual mean incoming radiation. Same as "AIns".
LonFromVEAtEpoch
Variable :
LonFromVEAtEpoch :real(DP), save
: �������������������� (��) (degree) Longitude of the planet at epoch (degree)
MaxItrEccAnomaly
Variable :
MaxItrEccAnomaly :integer, save
: �¢å�è¿��¹è���è¨�ç®�����������大繰��è¿�������. Maximum iteration number of times to calculate eccentric anomaly.
PerLonFromVE
Variable :
PerLonFromVE :real(DP), save
: �¥å������æ¸��£ã��è¿��¥ç�¹ã���åº� (è¿��¥ç�¹é�çµ�) (degree) Longitude of the perihelion from vernal equinox (degree)
PerpDistFromStarScld
Variable :
PerpDistFromStarScld :real(DP), save
: distance between a planet and a central star for perpetual experiment
PerpSinDel
Variable :
PerpSinDel :real(DP), save
: sine of declination angle for perpetual experiments
Subroutine :
SinDel :real(DP), intent(out)
: 赤緯 Declination
DistFromStarScld :real(DP), intent(out)
: è»����·å��å¾��§ã�¹ã�±ã�¼ã���³ã�°ã����������������� Distance from the star scaled by semimajor axis of the planet‘s orbit
PlanetLonFromVE :real(DP), intent(out)
: 中å�����中å�������座æ����������¥å���¹ã����æ¸��£ã���������åº� Longitude of the planet measured from the vernal equinox in the coordinate that the central star is located on the origin.

�­æ³¢�¥å� (å¤��½å�¥å�) ��è¨�ç®����¾ã��.

Calculate short wave (insolation) incoming radiation.

[Source]

  subroutine ShortIncomCalcOrbParam( SinDel, DistFromStarScld, PlanetLonFromVE )
    !
    ! �­æ³¢�¥å� (å¤��½å�¥å�) ��è¨�ç®����¾ã��.
    !
    ! Calculate short wave (insolation) incoming radiation. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! �¥ä������³æ���»ã������±ã��
    ! Date and time handler
    !
    use dc_calendar, only: DCCalInquire, DCCalDateChkLeapYear

    ! 宣�� ; Declaration statements
    !
    implicit none
    real(DP), intent(out) :: SinDel
                              ! 赤緯
                              ! Declination
    real(DP), intent(out) :: DistFromStarScld
                              ! è»����·å��å¾��§ã�¹ã�±ã�¼ã���³ã�°ã�����������������
                              ! Distance from the star scaled
                              ! by semimajor axis of the planet's orbit
    real(DP), intent(out) :: PlanetLonFromVE
                              ! 中å�����中å�������座æ����������¥å���¹ã����æ¸��£ã���������åº�
                              ! Longitude of the planet measured from the vernal equinox
                              ! in the coordinate that the central star is located on 
                              ! the origin.

    ! �業��
    ! Work variables
    !
    integer:: itr              ! �¤ã�����¼ã�·ã�§ã�³æ�¹å�������� DO ���¼ã�����業å���
                               ! Work variables for DO loop in iteration direction

    real(DP):: MeanAnomaly     ! å¹³å��è¿��¹è�
                               ! Mean anomaly
    real(DP):: EccAnomaly      ! �¢å�è¿��¹è�
                               ! eccentric anomaly
    real(DP):: EccAnomalyError ! ���¥ã�¼ã���³æ����������¢å�è¿��¹è����å·�
                               ! error of eccentric anomaly in Newton method
    real(DP):: TrueAnomaly     ! ���¹é�¢è�
                               ! true anomaly

    integer         :: hour_in_a_day, min_in_a_hour, day_in_a_year
    integer, pointer:: day_in_month_ptr(:) => null()
    real(DP)        :: sec_in_a_min, sec_in_a_day, sec_in_a_year



    ! ���� ; Executable statement
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. rad_short_income_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    ! å­£ç�å¤���, �¥å����������´å�����ç®�
    ! Calculate with seasonal change and diurnal change
    !
    call DCCalInquire( day_in_month_ptr = day_in_month_ptr , hour_in_day      = hour_in_a_day, min_in_hour      = min_in_a_hour, sec_in_min       = sec_in_a_min )
    ! Add 1 to day_in_month_ptr(2) if it is leap year.
    !
    if ( DCCalDateChkLeapYear( TimeN, InitialDate ) ) then
      day_in_month_ptr(2) = day_in_month_ptr(2) + 1
    end if

    day_in_a_year = sum( day_in_month_ptr )
    deallocate( day_in_month_ptr )
    sec_in_a_day  = hour_in_a_day * min_in_a_hour * sec_in_a_min
    sec_in_a_year = day_in_a_year * sec_in_a_day

    MeanAnomaly  = 2.0_DP * PI * ( TimeN - TimeAtEpoch ) / sec_in_a_year + ( LonFromVEAtEpoch - PerLonFromVE ) * PI / 180.0_DP
    MeanAnomaly  = mod( MeanAnomaly, 2.0_DP * PI )


    ! ���¥ã�¼ã���³æ���������¹³��è¿��¹è������¢å�è¿��¹è���æ±�����.
    ! Calculate eccentric anomaly from mean anomaly by using Newton method.

    EccAnomaly = MeanAnomaly
    do itr = 1, MaxItrEccAnomaly
      EccAnomalyError = EccAnomaly - Eccentricity * sin(EccAnomaly) - MeanAnomaly
      if ( abs(EccAnomalyError) <= ThreEccAnomalyError ) exit
      EccAnomaly      = EccAnomaly - EccAnomalyError / ( 1.0_DP - Eccentricity * cos(EccAnomaly) )
      EccAnomaly      = mod( EccAnomaly, 2.0 * PI )
    end do
    if ( itr > MaxItrEccAnomaly ) then
      call MessageNotify( 'E', module_name, 'Calculation for eccentric anomaly does not converge.' )
    end if

    DistFromStarScld = 1.0_DP - Eccentricity * cos( EccAnomaly )

    TrueAnomaly = 2.0_DP * atan( sqrt( ( 1.0d0 + Eccentricity ) / ( 1.0d0 - Eccentricity ) ) * tan( EccAnomaly / 2.0_DP ) )

    PlanetLonFromVE = TrueAnomaly + PerLonFromVE * PI / 180.0_DP
    PlanetLonFromVE = mod( PlanetLonFromVE, 2.0_DP * PI )

    SinDel = sin( EpsOrb * PI / 180.0_DP ) * sin( PlanetLonFromVE )


        ! code for debug
!!$        write( 60, * ) TimeN/sec_in_a_day, DCCalDateChkLeapYear(TimeN,date=InitialDate), day_in_a_year
!!$        write(  6, * ) TimeN/sec_in_a_day, DCCalDateChkLeapYear(TimeN,date=InitialDate), day_in_a_year
!!$        call flush( 60 )


!!$        write( 60, * ) TimeN/sec_in_a_day, asin(SinDel)*180.0/PI, DistFromStarScld, PlanetLonFromVE*180.0_DP/PI
!!$        write(  6, * ) TimeN/sec_in_a_day, asin(SinDel)*180.0/PI, DistFromStarScld, PlanetLonFromVE*180.0_DP/PI
!!$        call flush( 60 )


  end subroutine ShortIncomCalcOrbParam
SolDay
Variable :
SolDay :real(DP), save
: length of solar day
ThreEccAnomalyError
Variable :
ThreEccAnomalyError :real(DP), save
: �¢å�è¿��¹è���è¨�ç®����������å·���¨±å®¹ã��������. Threshold of error to calculate eccentric anomaly.
TimeAtEpoch
Variable :
TimeAtEpoch :real(DP), save
: ���������������� (sec) Time at epoch (sec)
module_name
Constant :
module_name = ‘rad_short_income :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
rad_short_income_inited
Variable :
rad_short_income_inited = .false. :logical, save
: ����設������. Initialization flag.
version
Constant :
version = ’$Name: $’ // ’$Id: rad_short_income.f90,v 1.6 2013/05/25 06:33:57 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version
xy_InAngle
Variable :
xy_InAngle(:,:) :real(DP), allocatable, save
: sec (�¥å�è§�). sec (angle of incidence)