1! { dg-do compile }
2! Structure constructor with component naming, test that an error is emitted
3! if there are arguments without name after ones with name.
4
5PROGRAM test
6  IMPLICIT NONE
7
8  ! Structure of basic data types
9  TYPE :: basics_t
10    INTEGER :: i
11    REAL :: r
12  END TYPE basics_t
13
14  TYPE(basics_t) :: basics
15
16  basics = basics_t (i=42, 1.5) ! { dg-error "Missing keyword name" }
17
18END PROGRAM test
19