-
Notifications
You must be signed in to change notification settings - Fork 0
/
vsf.f90
97 lines (65 loc) · 2.17 KB
/
vsf.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
! Last change: MG 20 Mar 2003 2:46 pm
SUBROUTINE vsf(lam,thetascat,coptlayer)
! Purpose:
! --------
! To randomly generate an angle based on the scattering phase function.
!
! Description
! -----------
!
! The subroutine will generate a random polar angle for a scattered
! photon based on a tabulated scattering phase function tabulated
! in the input file "spf.inp".
! The input file must be setup such that it is read as:
! "Probability of scatter up to, and including, angle thetascat"
!
! Record and revisions
! --------------------
! Date Programmer Description of change
! ==== ========== =====================
! 3/10/2003 Manuel Gimond Original code
USE rand_global
USE randmod
USE const_global
IMPLICIT NONE
INTEGER :: ii,jj
INTEGER, INTENT(IN) :: lam
INTEGER, INTENT(IN) :: coptlayer
REAL,INTENT(OUT) :: thetascat
REAL :: random
REAL :: dthetascat
thetascat = 0.0
jj = 2
TYPE_IF: IF (spftyp == 1) THEN ! Use SPF data read from file
! Determine which constituent is scattering for this interaction
random = rand()
FRACSCAT_DO: DO ii = 1, const
IF (random <= fracscat(lam, coptlayer, ii)) THEN
EXIT FRACSCAT_DO
END IF
END DO FRACSCAT_DO
random = rand()
IF (random <= spf(1,ii) ) THEN
dthetascat = spf(1,0)
thetascat = rand() * dthetascat
ELSE
ANGLE_LOOP: DO
IF (random > spf(jj - 1, ii) .AND. random <= spf(jj,ii) ) THEN
thetascat = spf(jj,0)
! A random value between 2 discrete SPF values can be generated.
! Uncomment the follwoing 2 lines if this option is desired
!
! dthetascat = spf(jj, 0) - spf(jj - 1, 0)
! thetascat = rand() * dthetascat + spf(jj - 1, 0)
!
! End of option
EXIT ANGLE_LOOP
ELSE
jj = jj + 1
END IF
END DO ANGLE_LOOP
END IF
ELSE
thetascat = ACOS( rand() * 2 - 1 )
END IF TYPE_IF
END SUBROUTINE vsf