process Function

recursive function process(iworkflow, irule, p) result(iaccepted)

process this part range starting with irule

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: iworkflow
integer, intent(in) :: irule
type(part), intent(in) :: p

Return Value integer(kind=ip)


Calls

proc~~process~2~~CallsGraph proc~process~2 problem_19b::process proc~process~2->proc~process~2 proc~get_accepted problem_19b::get_accepted proc~process~2->proc~get_accepted proc~workflow_name_to_index~2 problem_19b::workflow_name_to_index proc~process~2->proc~workflow_name_to_index~2

Called by

proc~~process~2~~CalledByGraph proc~process~2 problem_19b::process proc~process~2->proc~process~2 program~problem_19b problem_19b program~problem_19b->proc~process~2

Source Code

        recursive function process(iworkflow,irule,p) result(iaccepted)
            !! process this part range starting with irule

            integer,intent(in) :: iworkflow
            integer,intent(in) :: irule
            type(part),intent(in) :: p
            integer(ip) :: iaccepted

            integer(ip),dimension(:),allocatable :: itmp, itmp_t, itmp_f
            integer(ip) :: i
            type(part) :: pt, pf

            iaccepted = 0

            associate( r => workflows(iworkflow)%rules(irule) )

                ! check if we are done
                if (r%accept) then
                    iaccepted = get_accepted(p)
                    return
                else if (r%reject) then
                    iaccepted = 0
                    return
                end if

                ! process recursively, by splitting up the intervals when necessary

                if (r%operator>0) then
                    ! process the operator
                    select case (r%operator)
                    case(1) ! <

                        ! always create the two sets and process the two cases below
                        ! [note that some sets maybe empty]
                        !
                        ! example:
                        ![1,200]   < 10   ==> [1,9]    TRUE
                        !                     [10,200] FALSE

                        itmp = [(i, i=p%xmas(r%operator_arg)%v(1),p%xmas(r%operator_arg)%v(2))]
                        itmp_t = pack(itmp, mask = itmp<r%operator_val)  !true
                        itmp_f = pack(itmp, mask = itmp>=r%operator_val) !false

                        if (size(itmp_t)>0) then  ! some are true
                            pt = p
                            pt%xmas(r%operator_arg)%v = [itmp_t(1), itmp_t(size(itmp_t))]
                            if (r%goto=='A') then
                                iaccepted = iaccepted + get_accepted(pt)
                            else if (r%goto/='R') then
                                ! go to next workflow & start at first rule of new workflow
                                iaccepted = iaccepted + process(workflow_name_to_index(r%goto),1,pt)
                            end if
                        end if
                        if (size(itmp_f)>0) then  ! some are false
                            pf = p
                            pf%xmas(r%operator_arg)%v = [itmp_f(1), itmp_f(size(itmp_f))]
                            iaccepted = iaccepted + process(iworkflow,irule+1,pf) ! next rule
                        end if

                    case(2) ! >

                        itmp = [(i, i=p%xmas(r%operator_arg)%v(1),p%xmas(r%operator_arg)%v(2))]
                        itmp_t = pack(itmp, mask = itmp>r%operator_val)  !true
                        itmp_f = pack(itmp, mask = itmp<=r%operator_val) !false

                        if (size(itmp_t)>0) then  ! some are true
                            pt = p
                            pt%xmas(r%operator_arg)%v = [itmp_t(1), itmp_t(size(itmp_t))]
                            if (r%goto=='A') then
                                iaccepted = iaccepted + get_accepted(pt)
                            else if (r%goto/='R') then
                                ! go to next workflow & start at first rule of new workflow
                                iaccepted = iaccepted + process(workflow_name_to_index(r%goto),1,pt)
                            end if
                        end if
                        if (size(itmp_f)>0) then  ! some are false
                            pf = p
                            pf%xmas(r%operator_arg)%v = [itmp_f(1), itmp_f(size(itmp_f))]
                            iaccepted = iaccepted + process(iworkflow,irule+1,pf) ! next rule
                        end if

                    end select

                else
                    ! goto another workflow & start at first rule of new workflow
                    iaccepted = iaccepted + process(workflow_name_to_index(r%goto),1,p)
                end if
            end associate
            !end do

        end function process