xref: /llvm-project/flang/test/Examples/feature-list-class.f90 (revision 00d0749f92ece4b7bb4c7bc8f62c88f230f8710c)
1*00d0749fSEthan Luis McDonough! UNSUPPORTED: system-windows
2*00d0749fSEthan Luis McDonough! REQUIRES: plugins, shell, examples
3*00d0749fSEthan Luis McDonough
4*00d0749fSEthan Luis McDonough! RUN: %flang_fc1 -load %llvmshlibdir/flangFeatureList%pluginext \
5*00d0749fSEthan Luis McDonough! RUN:            -plugin feature-list %s 2>&1 | FileCheck %s
6*00d0749fSEthan Luis McDonough
7*00d0749fSEthan Luis McDonoughmodule list_features_test
8*00d0749fSEthan Luis McDonough    implicit none
9*00d0749fSEthan Luis McDonough
10*00d0749fSEthan Luis McDonough    type :: test_class_1
11*00d0749fSEthan Luis McDonough        integer :: a
12*00d0749fSEthan Luis McDonough        real :: b
13*00d0749fSEthan Luis McDonough    contains
14*00d0749fSEthan Luis McDonough        procedure :: sum => sum_test_class_1
15*00d0749fSEthan Luis McDonough        procedure :: set => set_values_test_class_1
16*00d0749fSEthan Luis McDonough    end type
17*00d0749fSEthan Luis McDonoughcontains
18*00d0749fSEthan Luis McDonough    real function sum_test_class_1(self)
19*00d0749fSEthan Luis McDonough        class(test_class_1), intent(in) :: self
20*00d0749fSEthan Luis McDonough        sum_test_class_1 = self%a + self%b
21*00d0749fSEthan Luis McDonough    end function
22*00d0749fSEthan Luis McDonough
23*00d0749fSEthan Luis McDonough    subroutine set_values_test_class_1(self, a, b)
24*00d0749fSEthan Luis McDonough        class(test_class_1), intent(out) :: self
25*00d0749fSEthan Luis McDonough        integer, intent(in) :: a, b
26*00d0749fSEthan Luis McDonough        self%a = a
27*00d0749fSEthan Luis McDonough        self%b = b
28*00d0749fSEthan Luis McDonough    end subroutine
29*00d0749fSEthan Luis McDonoughend module list_features_test
30*00d0749fSEthan Luis McDonough
31*00d0749fSEthan Luis McDonough! CHECK: Name: 32
32*00d0749fSEthan Luis McDonough! CHECK-NEXT: DataRef: 11
33*00d0749fSEthan Luis McDonough! CHECK-NEXT: Designator: 7
34*00d0749fSEthan Luis McDonough! CHECK-NEXT: DeclarationTypeSpec: 6
35*00d0749fSEthan Luis McDonough! CHECK-NEXT: Expr: 5
36*00d0749fSEthan Luis McDonough! CHECK-NEXT: DeclarationConstruct: 4
37*00d0749fSEthan Luis McDonough! CHECK-NEXT: EntityDecl: 4
38*00d0749fSEthan Luis McDonough! CHECK-NEXT: IntrinsicTypeSpec: 4
39*00d0749fSEthan Luis McDonough! CHECK-NEXT: SpecificationConstruct: 4
40*00d0749fSEthan Luis McDonough! CHECK-NEXT: StructureComponent: 4
41*00d0749fSEthan Luis McDonough! CHECK-NEXT: ActionStmt: 3
42*00d0749fSEthan Luis McDonough! CHECK-NEXT: AssignmentStmt: 3
43*00d0749fSEthan Luis McDonough! CHECK-NEXT: AttrSpec: 3
44*00d0749fSEthan Luis McDonough! CHECK-NEXT: DummyArg: 3
45*00d0749fSEthan Luis McDonough! CHECK-NEXT: ExecutableConstruct: 3
46*00d0749fSEthan Luis McDonough! CHECK-NEXT: ExecutionPartConstruct: 3
47*00d0749fSEthan Luis McDonough! CHECK-NEXT: ImplicitPart: 3
48*00d0749fSEthan Luis McDonough! CHECK-NEXT: IntentSpec: 3
49*00d0749fSEthan Luis McDonough! CHECK-NEXT: IntentSpec::Intent: 3
50*00d0749fSEthan Luis McDonough! CHECK-NEXT: SpecificationPart: 3
51*00d0749fSEthan Luis McDonough! CHECK-NEXT: TypeDeclarationStmt: 3
52*00d0749fSEthan Luis McDonough! CHECK-NEXT: Variable: 3
53*00d0749fSEthan Luis McDonough! CHECK-NEXT: Block: 2
54*00d0749fSEthan Luis McDonough! CHECK-NEXT: ComponentDecl: 2
55*00d0749fSEthan Luis McDonough! CHECK-NEXT: ComponentDefStmt: 2
56*00d0749fSEthan Luis McDonough! CHECK-NEXT: ComponentOrFill: 2
57*00d0749fSEthan Luis McDonough! CHECK-NEXT: ContainsStmt: 2
58*00d0749fSEthan Luis McDonough! CHECK-NEXT: DataComponentDefStmt: 2
59*00d0749fSEthan Luis McDonough! CHECK-NEXT: DeclarationTypeSpec::Class: 2
60*00d0749fSEthan Luis McDonough! CHECK-NEXT: DerivedTypeSpec: 2
61*00d0749fSEthan Luis McDonough! CHECK-NEXT: ExecutionPart: 2
62*00d0749fSEthan Luis McDonough! CHECK-NEXT: IntegerTypeSpec: 2
63*00d0749fSEthan Luis McDonough! CHECK-NEXT: IntrinsicTypeSpec::Real: 2
64*00d0749fSEthan Luis McDonough! CHECK-NEXT: ModuleSubprogram: 2
65*00d0749fSEthan Luis McDonough! CHECK-NEXT: TypeBoundProcBinding: 2
66*00d0749fSEthan Luis McDonough! CHECK-NEXT: TypeBoundProcDecl: 2
67*00d0749fSEthan Luis McDonough! CHECK-NEXT: TypeBoundProcedureStmt: 2
68*00d0749fSEthan Luis McDonough! CHECK-NEXT: TypeBoundProcedureStmt::WithoutInterface: 2
69*00d0749fSEthan Luis McDonough! CHECK-NEXT: DerivedTypeDef: 1
70*00d0749fSEthan Luis McDonough! CHECK-NEXT: DerivedTypeStmt: 1
71*00d0749fSEthan Luis McDonough! CHECK-NEXT: EndFunctionStmt: 1
72*00d0749fSEthan Luis McDonough! CHECK-NEXT: EndModuleStmt: 1
73*00d0749fSEthan Luis McDonough! CHECK-NEXT: EndSubroutineStmt: 1
74*00d0749fSEthan Luis McDonough! CHECK-NEXT: EndTypeStmt: 1
75*00d0749fSEthan Luis McDonough! CHECK-NEXT: Expr::Add: 1
76*00d0749fSEthan Luis McDonough! CHECK-NEXT: FunctionStmt: 1
77*00d0749fSEthan Luis McDonough! CHECK-NEXT: FunctionSubprogram: 1
78*00d0749fSEthan Luis McDonough! CHECK-NEXT: ImplicitPartStmt: 1
79*00d0749fSEthan Luis McDonough! CHECK-NEXT: ImplicitStmt: 1
80*00d0749fSEthan Luis McDonough! CHECK-NEXT: Module: 1
81*00d0749fSEthan Luis McDonough! CHECK-NEXT: ModuleStmt: 1
82*00d0749fSEthan Luis McDonough! CHECK-NEXT: ModuleSubprogramPart: 1
83*00d0749fSEthan Luis McDonough! CHECK-NEXT: PrefixSpec: 1
84*00d0749fSEthan Luis McDonough! CHECK-NEXT: Program: 1
85*00d0749fSEthan Luis McDonough! CHECK-NEXT: ProgramUnit: 1
86*00d0749fSEthan Luis McDonough! CHECK-NEXT: SubroutineStmt: 1
87*00d0749fSEthan Luis McDonough! CHECK-NEXT: SubroutineSubprogram: 1
88*00d0749fSEthan Luis McDonough! CHECK-NEXT: TypeBoundProcedurePart: 1
89