Assignment(=) - Defined Assignment

Statement: An interface block that defines generic assignment. The only procedures allowed in the interface block are subroutines that can be referenced as defined assignments.

The initial line for such an interface block takes the following form:

Syntax

INTERFACE ASSIGNMENT(=)

The subroutines within the interface block must have two nonoptional arguments, the first with intent OUT or INOUT, and the second with intent IN.

A defined assignment is treated as a reference to a subroutine. The left side of the assignment corresponds to the first dummy argument of the subroutine; the right side of the assignment corresponds to the second argument.

The ASSIGNMENT keyword extends or redefines an assignment operation if both sides of the equal sign are of the same derived type.

Defined elemental assignment is indicated by specifying ELEMENTAL in the SUBROUTINE statement.

Any procedure reference involving generic assignment must be resolvable to one specific procedure; it must be unambiguous. For more information, see Unambiguous Generic Procedure References.

Compatibility

CONSOLE STANDARD GRAPHICS QUICKWIN GRAPHICS WINDOWS DLL LIB

See Also: INTERFACE, Assignment Statements

Examples

The following is an example of a procedure interface block defining assignment:

INTERFACE ASSIGNMENT (=)
  SUBROUTINE BIT_TO_NUMERIC (NUM, BIT)
    INTEGER, INTENT(OUT) :: NUM
    LOGICAL, INTENT(IN)  :: BIT(:)
  END SUBROUTINE BIT_TO_NUMERIC

  SUBROUTINE CHAR_TO_STRING (STR, CHAR)
    USE STRING_MODULE                    ! Contains definition of type STRING
    TYPE(STRING), INTENT(OUT) :: STR     ! A variable-length string
    CHARACTER(*), INTENT(IN)  :: CHAR
  END SUBROUTINE  CHAR_TO_STRING
END  INTERFACE

The following example shows two equivalent ways to reference subroutine BIT_TO_NUMERIC:

  CALL BIT_TO_NUMERIC(X, (NUM(I:J)))
  X = NUM(I:J)

The following example shows two equivalent ways to reference subroutine CHAR_TO_STRING:

  CALL CHAR_TO_STRING(CH, '432C')
  CH = '432C'
!Converting circle data to interval data.
module mod1
TYPE CIRCLE
        REAL radius, center_point(2)
END TYPE CIRCLE
TYPE INTERVAL
        REAL lower_bound, upper_bound
END TYPE INTERVAL
CONTAINS
        SUBROUTINE circle_to_interval(I,C)
          type (interval),INTENT(OUT)::I
          type (circle),INTENT(IN)::C
!Project circle center onto the x=-axis
!Note: the length of the interval is the diameter of the circle
                I%lower_bound = C%center_point(1) - C%radius
                I%upper_bound = C%center_point(1) + C%radius
        END SUBROUTINE circle_to_interval
end module mod1

PROGRAM assign
use mod1
TYPE(CIRCLE) circle1
TYPE(INTERVAL) interval1
INTERFACE ASSIGNMENT(=)
        module procedure circle_to_interval
END INTERFACE
!Begin executable part of program
  circle1%radius = 2.5
  circle1%center_point = (/3.0,5.0/)
  interval1 = circle1
. . .
END PROGRAM