Ignore:
Timestamp:
Jan 21, 2014, 4:07:42 PM (11 years ago)
Author:
msylvestre
Message:

LMDZ.GENERIC/UNIVERSAL. rings shadow added in the case diurnal=.false. (daily average of the shadow)

File:
1 edited

Legend:

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

    r1133 r1161  
    4040    REAL, DIMENSION(:), ALLOCATABLE:: x, y, z ! cartesian coordinates of the points on the planet
    4141    REAL :: xs, ys, zs                        ! cartesian coordinates of the points of the subsolar point
    42     REAL, DIMENSION(:), ALLOCATABLE :: k      ! parameter (?)
     42    REAL, DIMENSION(:), ALLOCATABLE :: k
    4343    REAL, DIMENSION(:), ALLOCATABLE :: N      ! parameter to compute cartesian coordinates on a ellipsoidal planet
    4444    REAL, DIMENSION(:), ALLOCATABLE :: r      ! distance at which the incident ray of sun crosses the equatorial plane
     
    4848    ! equinox --> no shadow (AS: why is this needed?)
    4949    if(declin .eq. 0.) then
    50         eclipse = 0.
     50        eclipse(:) = 0.
    5151        return
    5252    endif
     
    6363    ALLOCATE(N(ngrid))
    6464    ALLOCATE(r(ngrid))
    65     eclipse = 2000.
     65    eclipse(:) = 2000.
    6666
    6767    ! Size of the rings
     
    8585
    8686    ! Convert to cartesian coordinates
    87     N = rad/sqrt(1-(e**2)*sinlat**2)
    88     x = N*coslat*coslon
    89     y = N*coslat*sinlon
    90     z = N*(1-e**2)*sinlat
     87    N(:) = rad / sqrt(1-(e**2)*sinlat(:)**2)
     88    x(:) = N(:)*coslat(:)*coslon(:)
     89    y(:) = N(:)*coslat(:)*sinlon(:)
     90    z(:) = N(:)*(1-e**2)*sinlat(:)
    9191
    9292! 2) LOCATION OF THE SUBSOLAR POINT
     
    9595    ! SG: the minus sign is important! ... otherwise subsolar point adopts a reverse rotation
    9696    phi_S = -(ptime - 0.5)*2.*pi
    97     write(*,*) 'subsol point coords : ', declin*180./pi, phi_S*180./pi
     97!    write(*,*) 'subsol point coords : ', declin*180./pi, phi_S*180./pi
    9898
    9999    ! subsolar latitude is declin (declination of the sun)
     
    106106! 3) WHERE DOES THE INCIDENT RAY OF SUN CROSS THE EQUATORIAL PLAN ?
    107107
    108     k = -z/zs
    109     r = (k*xs + x)**2 + (k*ys + y)**2
    110     r = sqrt(r)
     108    k(:) = -z(:)/zs
     109    r(:) = (k(:)*xs + x(:))**2 + (k(:)*ys + y(:))**2
     110    r(:) = sqrt(r(:))
    111111
    112112! 4) SO WHERE ARE THE SHADOW OF THESE RINGS ?
    113113
    114114    ! Summer hemisphere is not under the shadow of the rings
    115     where(lati*declin .gt. 0.)
    116        eclipse = 1000.
     115    where(lati(:)*declin .gt. 0.)
     116       eclipse(:) = 1000.
    117117    end where
    118118
    119119    ! No shadow of the rings by night
    120     where(x*xs + y*ys + z*zs .lt. 0.)
    121        eclipse = 1000.
     120    where(x(:)*xs + y(:)*ys + z(:)*zs .lt. 0.)
     121       eclipse(:) = 1000.
    122122    end where
    123123
    124124    ! if the incident rays of sun cross a ring, there is a shadow
    125125    do i=1, nb_A
    126         where(r .ge. A_Rint(i) .and. r .le. A_Rext(i) .and. eclipse .ne. 1000.)
    127             eclipse = 1. - exp(-tau_A(i)/cos(declin))
     126        where(r(:) .ge. A_Rint(i) .and. r(:) .le. A_Rext(i) .and. eclipse(:) .ne. 1000.)
     127            eclipse(:) = 1. - exp(-tau_A(i)/cos(declin))
    128128        end where
    129129    end do
    130130
    131131    do i=1, nb_B
    132         where(r .ge. B_Rint(i) .and. r .le. B_Rext(i) .and. eclipse .ne. 1000.)
    133             eclipse = 1. - exp(-tau_B(i)/cos(declin))
     132        where(r(:) .ge. B_Rint(i) .and. r(:) .le. B_Rext(i) .and. eclipse(:) .ne. 1000.)
     133            eclipse(:) = 1. - exp(-tau_B(i)/cos(declin))
    134134        end where
    135135    enddo
    136136   
    137137    do i=1, nb_C
    138         where(r .ge. C_Rint(i) .and. r .le. C_Rext(i) .and. eclipse .ne. 1000.)
    139             eclipse = 1. - exp(-tau_C(i)/cos(declin))
     138        where(r(:) .ge. C_Rint(i) .and. r(:) .le. C_Rext(i) .and. eclipse(:) .ne. 1000.)
     139            eclipse(:) = 1. - exp(-tau_C(i)/cos(declin))
    140140        end where
    141141    enddo
    142142
    143143    ! At the other places and the excluded ones, eclipse is 0.
    144     where(eclipse .eq. 2000. .or. eclipse .eq. 1000.)
    145         eclipse = 0.
     144    where(eclipse(:) .eq. 2000. .or. eclipse(:) .eq. 1000.)
     145        eclipse(:) = 0.
    146146    end where
    147147
Note: See TracChangeset for help on using the changeset viewer.