| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| real(kind=r64) | :: | A | ||||
| real(kind=r64) | :: | B | ||||
| real(kind=r64) | :: | P | ||||
| integer | :: | K | ||||
| real(kind=r64) | :: | IO | ||||
| real(kind=r64) | :: | IL | ||||
| real(kind=r64) | :: | RSER | ||||
| real(kind=r64) | :: | AA | ||||
| real(kind=r64) | :: | EPS | ||||
| integer | :: | KMAX | 
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE SEARCH(A,B,P,K,IO,IL,RSER,AA,EPS,KMAX)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Ø. Ulleberg, IFE Norway for Hydrogems
          !       DATE WRITTEN   March 2001
          !       MODIFIED       D. Bradley for use with EnergyPlus
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine minimum of an unimodal function with one variable. The algorithm was
          ! adapted to find the maximum power point of a PV module. The changes to the original
          ! algorithm are the following:
          ! 1. a subroutine "POWER" is called in order to calculate the power output of the PV module
          ! 2. the negative of the power of the PV module is taken so that the optimum can be found.
          ! METHODOLOGY EMPLOYED:
          ! na
          ! REFERENCES:
          !   /1/ MATHEWS, JOHN H.  NUMERICAL METHODS:  FORTRAN PROGRAMS. 1992, PP 413.
          !   /2/ NUMERICAL METHODS FOR MATHEMATICS, SCIENCE AND ENGINEERING, 2ND EDITION,
          !       PRENTICE HALL, NEW JERSEY, 1992.
          ! USE STATEMENTS:
          ! na
  IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  INTEGER K, KMAX
          ! SUBROUTINE PARAMETER DEFINITIONS:
  REAL(r64), PARAMETER :: DELTA=1.d-3
  REAL(r64), PARAMETER :: EPSILON=1.d-3
          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  REAL(r64) A,B,C,D,H,P,RONE,RTWO,YP,YA,YB,YC,YD
  REAL(r64) IO,IL,RSER,AA,EPS,IM,PM
  RONE=(SQRT(5.0d0)-1.d0)/2.d0
  RTWO=RONE*RONE
  H=B-A
  CALL POWER(IO,IL,RSER,AA,EPS,IM,A,PM)
  YA=-1.0d0*PM
  CALL POWER(IO,IL,RSER,AA,EPS,IM,B,PM)
  YB=-1.0d0*PM
  C=A+RTWO*H
  D=A+RONE*H
  CALL POWER(IO,IL,RSER,AA,EPS,IM,C,PM)
  YC=-1.0d0*PM
  CALL POWER(IO,IL,RSER,AA,EPS,IM,D,PM)
  YD=-1.0d0*PM
  K=1
  DO WHILE (ABS(YB-YA).GT.EPSILON .OR. H.GT.DELTA)
    IF (YC.LT.YD) THEN
      B=D
      YB=YD
      D=C
      YD=YC
      H=B-A
      C=A+RTWO*H
      CALL POWER(IO,IL,RSER,AA,EPS,IM,C,PM)
      YC=-1.0d0*PM
    ELSE
      A=C
      YA=YC
      C=D
      YC=YD
      H=B-A
      D=A+RONE*H
      CALL POWER(IO,IL,RSER,AA,EPS,IM,D,PM)
      YD=-1.0d0*PM
    ENDIF
    K=K+1
  END DO
  IF (K.LT.KMAX) THEN
    P=A
    YP=YA
    IF (YB.LT.YA) THEN
      P=B
      YP=YB
    ENDIF
    RETURN
  ELSE
    RETURN
  ENDIF
  END SUBROUTINE SEARCH