parse_detectors Subroutine

public subroutine parse_detectors(table, dects, context, error)

parse the detectors

Arguments

Type IntentOptional Attributes Name
type(toml_table), intent(inout) :: table

Input Toml table

type(dect_array), intent(out), allocatable :: dects(:)

Detector array to be filled.

type(toml_context), intent(in) :: context

Context handle for error reporting.

type(toml_error), intent(out), allocatable :: error

Error message


Source Code

    subroutine parse_detectors(table, dects, context, error)
        !! parse the detectors

        use detectors,     only : dect_array, circle_dect, annulus_dect, camera
        use sim_state_mod, only : state

        !> Input Toml table
        type(toml_table),               intent(inout) :: table
        !> Detector array to be filled.
        type(dect_array), allocatable,  intent(out)   :: dects(:)
        !> Context handle for error reporting.
        type(toml_context),             intent(in)    :: context
        !> Error message
        type(toml_error),  allocatable, intent(out)   :: error

        type(toml_array), pointer :: array
        type(toml_table), pointer :: child
        character(len=:), allocatable :: dect_type
        type(circle_dect), target, save, allocatable :: dect_c(:)
        type(annulus_dect), target, save, allocatable :: dect_a(:)
        type(camera), target, save, allocatable :: dect_cam(:)
        integer :: i, c_counter, a_counter, cam_counter, j, k,origin

        c_counter = 0
        a_counter = 0
        cam_counter = 0
        call get_value(table, "detectors", array)
        allocate(dects(len(array)))

        do i = 1, len(array)
            call get_value(array, i, child)
            call get_value(child, "type", dect_type, origin=origin)
            select case(dect_type)
            case default
                call make_error(error, &
                    context%report("Invalid detector type. Valid types are [circle, annulus, camera]", &
                    origin, "expected valid detector type"), -1)
                return
            case("circle")
                c_counter = c_counter + 1
            case("annulus")
                a_counter = a_counter + 1
            case("camera")
                cam_counter = cam_counter + 1
            end select
        end do

        if(c_counter > 0)then
            if(allocated(dect_c))deallocate(dect_c)
            allocate(dect_c(c_counter))
        end if
        if(a_counter > 0)then
            if(allocated(dect_a))deallocate(dect_a)
            allocate(dect_a(a_counter))
        end if
        if(cam_counter > 0)then
            if(allocated(dect_cam))deallocate(dect_cam)
            allocate(dect_cam(cam_counter))
        end if
        c_counter = 1
        a_counter = 1
        cam_counter = 1
        state%trackHistory=.false.
        do i = 1, len(array)
            call get_value(array, i, child)
            call get_value(child, "type", dect_type)
            call get_value(child, "historyFileName", state%historyFilename, "photPos.obj")
            select case(dect_type)
            case("circle")
                call handle_circle_dect(child, dect_c, c_counter, context, error)
                if(allocated(error))return
            case("annulus")
                call handle_annulus_dect(child, dect_a, a_counter, context, error)
                if(allocated(error))return
            case("camera")
                call handle_camera(child, dect_cam, cam_counter, context, error)
                if(allocated(error))return
            end select
        end do

        do i = 1, c_counter-1
            allocate(dects(i)%p, source=dect_c(i))
            dects(i)%p => dect_c(i)
        end do

        do j = 1, a_counter-1
            allocate(dects(j+i-1)%p, source=dect_a(j))
            dects(j+i-1)%p => dect_a(j)
        end do

        do k = 1, cam_counter-1
            allocate(dects(j+i+k-2)%p, source=dect_cam(k))
            dects(j+i+k-2)%p => dect_cam(k)
        end do

        if(.not. allocated(state%historyFilename))state%historyFilename="photPos.obj"

    end subroutine parse_detectors