File: interface3.f90

package info (click to toggle)
lfortran 0.45.0-1
  • links: PTS, VCS
  • area: main
  • in suites: sid, trixie
  • size: 46,332 kB
  • sloc: cpp: 137,068; f90: 51,260; python: 6,444; ansic: 4,277; yacc: 2,285; fortran: 806; sh: 524; makefile: 30; javascript: 15
file content (96 lines) | stat: -rw-r--r-- 2,182 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
module interface3
implicit none
!checks the syntax
public :: x, y, z, assignment(=), operator(+), operator(.and.), operator(.in.)
public :: operator(*)
public :: operator(/)
public :: operator(/ )
public :: operator(// )

interface
    module procedure sample
end interface

interface A
    module procedure :: sample
end interface A

INTERFACE ASSIGNMENT ( = )
    SUBROUTINE LOGICAL_TO_NUMERIC (N, B)
    INTEGER, INTENT (OUT) :: N
    LOGICAL, INTENT (IN) :: B
    END SUBROUTINE LOGICAL_TO_NUMERIC
END INTERFACE ASSIGNMENT ( = )

interface operator (+)
    module procedure union
end interface operator (+)
interface operator (-)
    module procedure difference
end interface operator (-)
interface operator (*)
    module procedure intersection
end interface operator (*)
interface operator ( / )
end interface operator ( / )
interface operator (/)
end interface operator (/)
interface operator (**)
end interface operator (**)
interface operator (==)
end interface operator (==)
interface operator (/=)
end interface operator (/=)
interface operator (>)
end interface operator (>)
interface operator (>=)
end interface operator (>=)
interface operator (<)
end interface operator (<)
interface operator (<=)
    module procedure subset
end interface operator (<=)
interface operator (.not.)
end interface operator (.not.)
interface operator (.and.)
end interface operator (.and.)
interface operator (.or.)
end interface operator (.or.)
interface operator (.eqv.)
end interface operator (.eqv.)
interface operator (.neqv.)
end interface operator (.neqv.)

abstract interface
end interface

public :: operator(//)

interface operator (//)
end interface  operator (//)

interface write(formatted)
    module procedure :: write_formatted
end interface

interface write(unformatted)
    module procedure :: write_unformatted
end interface

interface read(formatted)
    module procedure :: read_formatted
end interface

interface read(unformatted)
    module procedure :: read_unformatted
end interface

contains

    function f(operator)
    ! Currently parsed as an operator, but AST -> ASR phase can fix that:
    real, intent(in) :: operator (*)
    end function f


end module