! $Id$ ! ! module science_tools_mod contains subroutine compute_emis ( bt_11um , rad, sensor , ch_num & & , emis ) use planck_mod implicit none real, intent(in) :: bt_11um (:,:) real, intent(in) :: rad (:,:) character(len=10) , intent(in) :: sensor integer, intent(in) :: ch_num real, intent(out) :: emis (:,:) real, allocatable :: rad_bt11um_in_chn20 (:,:) ! --- executable allocate ( rad_bt11um_in_chn20 ( size(rad,1), size(rad,2) ) ) call planck_rad ( bt_11um , sensor, ch_num , rad_bt11um_in_chn20) emis = rad / rad_bt11um_in_chn20 deallocate ( rad_bt11um_in_chn20 ) end subroutine !------------------------------------------------------------------------- ! subroutine LOCATE(xx, n, x, j) ! Numerical recipes bisection search - x will be between xx(j) and xx(j+1) !-------------------------------------------------------------------------- subroutine LOCATE(xx, n, x, j) ! Arguments integer, intent(in) :: n integer, intent(out) :: j real, intent(in) :: x real , dimension(:), intent(in) :: xx ! Local variables integer :: i, jl, jm, ju jl = 0 ju = n + 1 do i = 1, 2*n if (ju-jl <= 1) then exit endif jm = (ju + jl) / 2 if ((xx(n) >= xx(1)) .eqv. (x >= xx(jm))) then jl = jm else ju = jm endif enddo if (x == xx(1)) then j=1 else if (x == xx(n)) then j = n - 1 else j = jl endif end subroutine LOCATE end module science_tools_mod