Skip to content

Commit

Permalink
Revert all instances of Spixel%Illum to SPixel%Illum.
Browse files Browse the repository at this point in the history
  • Loading branch information
andyprata committed Aug 16, 2021
1 parent 7570f0e commit a2612fb
Show file tree
Hide file tree
Showing 3 changed files with 52 additions and 52 deletions.
98 changes: 49 additions & 49 deletions src/get_indexing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -132,22 +132,22 @@ subroutine Get_Indexing(Ctrl, SAD_Chan, SPixel, MSI_Data, status)
! and/or are flagged as missing.
is_not_used_or_missing = .false.

if (Spixel%Illum .eq. IDay) then
if (SPixel%Illum .eq. IDay) then
! All channels are used
do i_chan = 1, Ctrl%Ind%Ny
if (MSI_Data%MSI(SPixel%Loc%X0, SPixel%Loc%Y0, i_chan) == sreal_fill_value) then
is_not_used_or_missing(i_chan) = .true.
end if
end do
else if (Spixel%Illum .eq. ITwi) then
else if (SPixel%Illum .eq. ITwi) then
! Only pure thermal channels (no mixed) are used
do i_chan = 1, Ctrl%Ind%Ny
if (btest(Ctrl%Ind%Ch_Is(i_chan), SolarBit) .or. &
MSI_Data%MSI(SPixel%Loc%X0, SPixel%Loc%Y0, i_chan) == sreal_fill_value) then
is_not_used_or_missing(i_chan) = .true.
end if
end do
else if (Spixel%Illum .eq. INight) then
else if (SPixel%Illum .eq. INight) then
! All thermal channels (including mixed) are used
do i_chan = 1, Ctrl%Ind%Ny
if (.not. btest(Ctrl%Ind%Ch_Is(i_chan), ThermalBit) .or. &
Expand All @@ -164,7 +164,7 @@ subroutine Get_Indexing(Ctrl, SAD_Chan, SPixel, MSI_Data, status)
select case (Ctrl%Approach)
case (AppCld1L)
if (.not. Ctrl%do_new_night_retrieval &
.or. Spixel%Illum .eq. IDay .or. Spixel%Illum .eq. ITwi) then
.or. SPixel%Illum .eq. IDay .or. SPixel%Illum .eq. ITwi) then
call cloud_indexing_logic(Ctrl, SPixel, is_not_used_or_missing, &
X, XJ, XI, status)
else
Expand Down Expand Up @@ -212,8 +212,8 @@ subroutine Get_Indexing(Ctrl, SAD_Chan, SPixel, MSI_Data, status)
end if

! Set the illumination-dependent first guess and a priori
SPixel%FG = Ctrl%FG(:,Spixel%Illum)
SPixel%AP = Ctrl%AP(:,Spixel%Illum)
SPixel%FG = Ctrl%FG(:,SPixel%Illum)
SPixel%AP = Ctrl%AP(:,SPixel%Illum)

! Set up all the channel indexes
call setup_indexes(Ctrl, SAD_Chan, SPixel, is_not_used_or_missing)
Expand Down Expand Up @@ -267,13 +267,13 @@ subroutine setup_indexes(Ctrl, SAD_Chan, SPixel, is_not_used_or_missing)
SPixel%Ind%Ny = SPixel%Ind%Ny + 1

if (btest(Ctrl%Ind%Ch_Is(i), SolarBit) .and. &
Spixel%Illum .eq. IDay .and. &
SPixel%Illum .eq. IDay .and. &
btest(Ctrl%Ind%Ch_Is(i), ThermalBit)) then
SPixel%Ind%NMixed = SPixel%Ind%NMixed + 1
end if

if (btest(Ctrl%Ind%Ch_Is(i), SolarBit) .and. &
Spixel%Illum .eq. IDay) then
SPixel%Illum .eq. IDay) then
SPixel%Ind%NSolar = SPixel%Ind%NSolar + 1
end if

Expand Down Expand Up @@ -315,7 +315,7 @@ subroutine setup_indexes(Ctrl, SAD_Chan, SPixel, is_not_used_or_missing)
cycle

if (btest(Ctrl%Ind%Ch_Is(i), SolarBit) .and. &
Spixel%Illum .eq. IDay .and. &
SPixel%Illum .eq. IDay .and. &
btest(Ctrl%Ind%Ch_Is(i), ThermalBit)) then
! Mixed channels out of those to be retrieved
SPixel%Ind%YMixed(i2) = ii
Expand All @@ -325,7 +325,7 @@ subroutine setup_indexes(Ctrl, SAD_Chan, SPixel, is_not_used_or_missing)
end if

if (btest(Ctrl%Ind%Ch_Is(i), SolarBit) .and. &
Spixel%Illum .eq. IDay) then
SPixel%Illum .eq. IDay) then
! Solar channels out of those to be used
SPixel%Ind%YSolar(i0) = ii
SPixel%spixel_y_solar_to_ctrl_y_index(i0) = i
Expand Down Expand Up @@ -489,7 +489,7 @@ subroutine cloud_indexing_logic(Ctrl, SPixel, is_not_used_or_missing, &
! channels then pick the first one in Ctrl%ReChans that matches and set the
! rest of the Ctrl%ReChans that match to missing. If Ctrl%ReChans is not
! associated it is assumed that all available r_e channels should be used.
if (Spixel%Illum .eq. IDay .and. associated(Ctrl%ReChans)) then
if (SPixel%Illum .eq. IDay .and. associated(Ctrl%ReChans)) then
i_r_e_chan = 0
do i_chan = 1, size(Ctrl%ReChans)
ii_chan = find_in_array(Ctrl%r_e_chans, Ctrl%ReChans(i_chan))
Expand Down Expand Up @@ -550,29 +550,29 @@ subroutine cloud_indexing_logic(Ctrl, SPixel, is_not_used_or_missing, &
ii_xi = 0
n_ir_chans2 = n_ir_chans
! Retrieve Tau if sufficient appropriate channels are available
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, &
active = n_tau_chans .ge. min_tau_chans)
! Retrieve Re if sufficient appropriate channels are available (if thermal
! channels used, decrement the IR channel counter)
if (re_thermal) then
call Add_to_State_Vector(Ctrl, Spixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, &
active = n_r_e_chans .ge. min_r_e_chans, ch_available = n_ir_chans2)
else
call Add_to_State_Vector(Ctrl, Spixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, &
active = n_r_e_chans .ge. min_r_e_chans)
end if
! Pc, Ts, Fr retreved for all illumination. n_ir_chans2 ensures there aren't
! more things retrieved than there are measurements
call Add_to_State_Vector(Ctrl, Spixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, &
active = n_ir_chans2 .ge. min_ir_chans, ch_available = n_ir_chans2)
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, &
active = n_ir_chans2 .ge. min_ir_chans, ch_available = n_ir_chans2)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IFr, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IFr, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, &
active = n_ir_chans2 .ge. min_ir_chans, ch_available = n_ir_chans2)

Expand All @@ -582,7 +582,7 @@ subroutine cloud_indexing_logic(Ctrl, SPixel, is_not_used_or_missing, &
else
min_rho = MaxRho_XX
end if
call Identify_BRDF_Terms(Ctrl, Spixel%Illum, 1, min_rho, &
call Identify_BRDF_Terms(Ctrl, SPixel%Illum, 1, min_rho, &
is_not_used_or_missing, X, ii_x, XJ, ii_xj, XI, ii_xi, &
SPixel%variables_retrieved, .false.)

Expand Down Expand Up @@ -653,44 +653,44 @@ subroutine cloud_indexing_logic_night(Ctrl, SPixel, is_not_used_or_missing, &
ii_xi = 0

if (n_chans .eq. 1) then
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .false.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .false.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .false.)
else if (n_chans .eq. 2) then
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .false.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .false.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
else if (n_chans .eq. 3) then
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
else if (n_chans .ge. 4) then
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
end if

call Add_to_State_Vector(Ctrl, Spixel%Illum, IFr, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IFr, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .false.)

! Add BRDF terms to parameter vector
Expand All @@ -699,7 +699,7 @@ subroutine cloud_indexing_logic_night(Ctrl, SPixel, is_not_used_or_missing, &
else
min_rho = MaxRho_XX
end if
call Identify_BRDF_Terms(Ctrl, Spixel%Illum, 1, min_rho, &
call Identify_BRDF_Terms(Ctrl, SPixel%Illum, 1, min_rho, &
is_not_used_or_missing, X, ii_x, XJ, ii_xj, XI, ii_xi, &
SPixel%variables_retrieved, .false.)

Expand Down Expand Up @@ -763,24 +763,24 @@ subroutine cloud_indexing_logic_two_layer(Ctrl, SPixel, is_not_used_or_missing,
ii_xj = 0
ii_xi = 0

call Add_to_State_Vector(Ctrl, Spixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITau, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IRe, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IPc, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITau2, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITau2, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IRe2, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IRe2, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IPc2, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IPc2, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, ITs, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .true.)

call Add_to_State_Vector(Ctrl, Spixel%Illum, IFr, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IFr, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .false.)
call Add_to_State_Vector(Ctrl, Spixel%Illum, IFr2, X, ii_x, XJ, ii_xj, &
call Add_to_State_Vector(Ctrl, SPixel%Illum, IFr2, X, ii_x, XJ, ii_xj, &
XI, ii_xi, SPixel%variables_retrieved, active = .false.)

! Add BRDF terms to parameter vector
Expand All @@ -789,7 +789,7 @@ subroutine cloud_indexing_logic_two_layer(Ctrl, SPixel, is_not_used_or_missing,
else
min_rho = MaxRho_XX
end if
call Identify_BRDF_Terms(Ctrl, Spixel%Illum, 1, min_rho, &
call Identify_BRDF_Terms(Ctrl, SPixel%Illum, 1, min_rho, &
is_not_used_or_missing, X, ii_x, XJ, ii_xj, XI, ii_xi, &
SPixel%variables_retrieved, .false.)

Expand Down Expand Up @@ -844,7 +844,7 @@ subroutine aer_indexing_logic(Ctrl, SPixel, is_not_used_or_missing, &


! Daytime only
if (Spixel%Illum /= IDay) then
if (SPixel%Illum /= IDay) then
status = SPixelIndexing
return
end if
Expand Down Expand Up @@ -934,7 +934,7 @@ subroutine swan_indexing_logic(Ctrl, SPixel, is_not_used_or_missing, &


! Daytime only
if (Spixel%Illum /= IDay) then
if (SPixel%Illum /= IDay) then
status = SPixelIndexing
return
end if
Expand Down Expand Up @@ -1067,7 +1067,7 @@ subroutine aer_indexing_logic_1view(Ctrl, SPixel, is_not_used_or_missing, &
integer, parameter :: min_view = 1 ! Only using a single view.

! Daytime only
if (Spixel%Illum /= IDay) then
if (SPixel%Illum /= IDay) then
status = SPixelIndexing
return
end if
Expand Down
4 changes: 2 additions & 2 deletions src/get_measurements.F90
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ subroutine Get_Measurements(Ctrl, SAD_Chan, SPixel, MSI_Data, status)
end if

! Daylight
if (Spixel%Illum .ne. INight .and. Spixel%Illum .ne. ITwi) then
if (SPixel%Illum .ne. INight .and. SPixel%Illum .ne. ITwi) then
if (SAD_Chan(ii)%Solar%Flag /= 0) then
if (SAD_Chan(ii)%Thermal%Flag /= 0) then
! Both solar and thermal => mixed
Expand Down Expand Up @@ -228,7 +228,7 @@ subroutine Get_Measurements(Ctrl, SAD_Chan, SPixel, MSI_Data, status)
ii = SPixel%spixel_y_to_ctrl_y_index(i)

! Daylight
if (Spixel%Illum == IDay) then
if (SPixel%Illum == IDay) then
if (SAD_Chan(ii)%Solar%Flag /= 0) then
if (SAD_Chan(ii)%Thermal%Flag /= 0) then
! both solar and thermal => mixed
Expand Down
2 changes: 1 addition & 1 deletion src/x_mdad.F90
Original file line number Diff line number Diff line change
Expand Up @@ -144,7 +144,7 @@ subroutine X_MDAD(Ctrl, SPixel, index, X, status, Err)

case (ITau, ITau2) ! Cloud optical depth, Tau

if (Spixel%Illum == IDay .and. i_spixel_06_solar > 0) then
if (SPixel%Illum == IDay .and. i_spixel_06_solar > 0) then
! Calculate overcast reflectance (assuming fully cloudy pixel).
! Uses channel nearest 0.67 microns, index Ctrl%Ind%MDAD_SW.
Ref_o = SPixel%Ym(i_spixel_06) - SPixel%Surface%Rs(i_spixel_06_solar)
Expand Down

0 comments on commit a2612fb

Please sign in to comment.