MODULE Search_Routines CONTAINS !-LinearSearch------------------------------------------------ ! Subroutine to search the list Item for ItemSought using ! linear search. If ItemSought is found in the list, Found ! is returned as true and the Location of the item is ! returned; otherwise Found is false. ! ! Accepts: Array Item and ItemSought ! Returns: If ItemSought is found in the list Item: ! Found = true and ! Location = position of ItemSought ! Otherwise: ! Found = false ! (and Location = last position examined) ! ! Note: Item is an assumed-shape array so a program unit ! that calls this subroutine must: ! 1. contain this subroutine as an internal subprogram, ! 2. import this subroutine from a module, or ! 3. contain an interface block for this subroutine. !------------------------------------------------------------- SUBROUTINE LinearSearch(Item, ItemSought, Found, Location) CHARACTER(*), DIMENSION(:), INTENT(IN) :: Item CHARACTER(*), INTENT(IN) :: ItemSought LOGICAL, INTENT(OUT) :: Found INTEGER, INTENT(OUT) :: Location INTEGER :: NumItems NumItems = SIZE(Item) Location = 1 Found = .FALSE. ! While Location less than or equal to NumItems and not Found do DO IF ((Location > NumItems) .OR. Found) RETURN ! If end of list reached or item found, terminate the search ! Otherwise check the next list element IF (ItemSought == Item(Location)) THEN Found = .TRUE. ELSE Location = Location + 1 END IF END DO END SUBROUTINE LinearSearch !-BinarySearch------------------------------------------------ ! Subroutine to search the list Item for ItemSought using ! binary search. If ItemSought is found in the list, Found ! is returned as true and the Location of the item is ! returned; otherwise Found is false. In this version of ! binary search, ItemSought and the elements of Item are ! character strings. Local variables used are: ! First : first item in (sub)list being searched ! Last : last " " " " " ! Middle : middle " " " " " ! ! Accepts: Array Item and ItemSought in the list Item ! Returns: If ItemSought is found: ! Found = true and ! Location = position of ItemSought ! Otherwise: ! Found = false (and Location = last ! position examined) ! ! Note: Item is an assumed-shape array so a program unit ! that calls this subroutine must: ! 1. contain this subroutine as an internal subprogram, ! 2. import this subroutine from a module, or ! 3. contain an interface block for this subroutine. !------------------------------------------------------------- SUBROUTINE BinarySearch(Item, ItemSought, Found, Location) CHARACTER(*), DIMENSION(:), INTENT(IN) :: Item CHARACTER(*), INTENT(IN) :: ItemSought LOGICAL, INTENT(OUT) :: Found INTEGER, INTENT(OUT) :: Location INTEGER :: First, Last, Middle First = 1 Last = SIZE(Item) Found = .FALSE. ! While First less than or equal to Last and not Found do DO IF ((First > Last) .OR. Found) RETURN ! If empty list to be searched or item found, return ! Otherwise continue with the following Middle = (First + Last) / 2 IF (ItemSought < Item(Middle)) THEN Last = Middle - 1 ELSE IF (ItemSought > Item(Middle)) THEN First = Middle + 1 ELSE Found = .TRUE. Location = Middle END IF END DO END SUBROUTINE BinarySearch END MODULE Search_Routines