diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index f3239d761022d4674741dd27f63277d231f4f7ab..91697532ca4141aa2cf6f175c1d74ad14031d8ad 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,12 @@
+2018-10-25  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/87725
+	* openmp.c (gfc_match_omp_clauses): Parse simd, monotonic and
+	nonmonotonic modifiers regardless of if they have been parsed
+	already or if the opposite one has.  Fix up check whether
+	comma after modifier should be parsed.
+	(resolve_omp_clauses): Diagnose schedule modifier restrictions.
+
 2018-10-23  Paul Thomas  <pault@gcc.gnu.org>
 
 	PR fortran/85603
diff --git a/gcc/fortran/openmp.c b/gcc/fortran/openmp.c
index bd83733580e64f22e5ede34dbeac1447d1297475..6430e61ea7a670d3b706a893e96937cc743772b8 100644
--- a/gcc/fortran/openmp.c
+++ b/gcc/fortran/openmp.c
@@ -1710,22 +1710,17 @@ gfc_match_omp_clauses (gfc_omp_clauses **cp, const omp_mask mask,
 	      locus old_loc2 = gfc_current_locus;
 	      do
 		{
-		  if (!c->sched_simd
-		      && gfc_match ("simd") == MATCH_YES)
+		  if (gfc_match ("simd") == MATCH_YES)
 		    {
 		      c->sched_simd = true;
 		      nmodifiers++;
 		    }
-		  else if (!c->sched_monotonic
-			   && !c->sched_nonmonotonic
-			   && gfc_match ("monotonic") == MATCH_YES)
+		  else if (gfc_match ("monotonic") == MATCH_YES)
 		    {
 		      c->sched_monotonic = true;
 		      nmodifiers++;
 		    }
-		  else if (!c->sched_monotonic
-			   && !c->sched_nonmonotonic
-			   && gfc_match ("nonmonotonic") == MATCH_YES)
+		  else if (gfc_match ("nonmonotonic") == MATCH_YES)
 		    {
 		      c->sched_nonmonotonic = true;
 		      nmodifiers++;
@@ -1736,7 +1731,7 @@ gfc_match_omp_clauses (gfc_omp_clauses **cp, const omp_mask mask,
 			gfc_current_locus = old_loc2;
 		      break;
 		    }
-		  if (nmodifiers == 0
+		  if (nmodifiers == 1
 		      && gfc_match (" , ") == MATCH_YES)
 		    continue;
 		  else if (gfc_match (" : ") == MATCH_YES)
@@ -4075,6 +4070,30 @@ resolve_omp_clauses (gfc_code *code, gfc_omp_clauses *omp_clauses,
 	gfc_warning (0, "INTEGER expression of SCHEDULE clause's chunk_size "
 		     "at %L must be positive", &expr->where);
     }
+  if (omp_clauses->sched_kind != OMP_SCHED_NONE
+      && omp_clauses->sched_nonmonotonic)
+    {
+      if (omp_clauses->sched_kind != OMP_SCHED_DYNAMIC
+	  && omp_clauses->sched_kind != OMP_SCHED_GUIDED)
+	{
+	  const char *p;
+	  switch (omp_clauses->sched_kind)
+	    {
+	    case OMP_SCHED_STATIC: p = "STATIC"; break;
+	    case OMP_SCHED_RUNTIME: p = "RUNTIME"; break;
+	    case OMP_SCHED_AUTO: p = "AUTO"; break;
+	    default: gcc_unreachable ();
+	    }
+	  gfc_error ("NONMONOTONIC modifier specified for %s schedule kind "
+		     "at %L", p, &code->loc);
+	}
+      else if (omp_clauses->sched_monotonic)
+	gfc_error ("Both MONOTONIC and NONMONOTONIC schedule modifiers "
+		   "specified at %L", &code->loc);
+      else if (omp_clauses->ordered)
+	gfc_error ("NONMONOTONIC schedule modifier specified with ORDERED "
+		   "clause at %L", &code->loc);
+    }
 
   /* Check that no symbol appears on multiple clauses, except that
      a symbol can appear on both firstprivate and lastprivate.  */
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 54334c9717deeee3db7d3251d0bab9919db62033..94496cd30a7fde61e4a745264fe14f8a6dcb2f5d 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,11 @@
+2018-10-25  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/87725
+	* c-c++-common/gomp/schedule-modifiers-1.c (bar): Separate modifier
+	from kind with a colon rather than comma.
+	* gfortran.dg/gomp/schedule-modifiers-1.f90: New test.
+	* gfortran.dg/gomp/schedule-modifiers-2.f90: New test.
+
 2018-10-24  Michael Meissner  <meissner@linux.ibm.com>
 
 	* gcc.target/powerpc/float128-math.c: New test to make sure the
diff --git a/gcc/testsuite/c-c++-common/gomp/schedule-modifiers-1.c b/gcc/testsuite/c-c++-common/gomp/schedule-modifiers-1.c
index 7edea1b147cca4fa83a63febc59975e85f2a2ccc..33ca3a6534d7c0549c9adba708f00e535b522f2b 100644
--- a/gcc/testsuite/c-c++-common/gomp/schedule-modifiers-1.c
+++ b/gcc/testsuite/c-c++-common/gomp/schedule-modifiers-1.c
@@ -80,21 +80,21 @@ bar (void)
   #pragma omp for schedule (nonmonotonic : auto)	/* { dg-error ".nonmonotonic. modifier specified for .auto. schedule kind" } */
   for (i = 0; i < 64; i++)
     ;
-  #pragma omp for schedule (nonmonotonic, dynamic) ordered	/* { dg-error ".nonmonotonic. schedule modifier specified together with .ordered. clause" } */
+  #pragma omp for schedule (nonmonotonic : dynamic) ordered	/* { dg-error ".nonmonotonic. schedule modifier specified together with .ordered. clause" } */
   for (i = 0; i < 64; i++)
     #pragma omp ordered
       ;
-  #pragma omp for ordered schedule(nonmonotonic, dynamic, 5)	/* { dg-error ".nonmonotonic. schedule modifier specified together with .ordered. clause" } */
+  #pragma omp for ordered schedule(nonmonotonic : dynamic, 5)	/* { dg-error ".nonmonotonic. schedule modifier specified together with .ordered. clause" } */
   for (i = 0; i < 64; i++)
     #pragma omp ordered
       ;
-  #pragma omp for schedule (nonmonotonic, guided) ordered(1)	/* { dg-error ".nonmonotonic. schedule modifier specified together with .ordered. clause" } */
+  #pragma omp for schedule (nonmonotonic : guided) ordered(1)	/* { dg-error ".nonmonotonic. schedule modifier specified together with .ordered. clause" } */
   for (i = 0; i < 64; i++)
     {
       #pragma omp ordered depend(sink: i - 1)
       #pragma omp ordered depend(source)
     }
-  #pragma omp for ordered(1) schedule(nonmonotonic, guided, 2)	/* { dg-error ".nonmonotonic. schedule modifier specified together with .ordered. clause" } */
+  #pragma omp for ordered(1) schedule(nonmonotonic : guided, 2)	/* { dg-error ".nonmonotonic. schedule modifier specified together with .ordered. clause" } */
   for (i = 0; i < 64; i++)
     {
       #pragma omp ordered depend(source)
diff --git a/gcc/testsuite/gfortran.dg/gomp/schedule-modifiers-1.f90 b/gcc/testsuite/gfortran.dg/gomp/schedule-modifiers-1.f90
new file mode 100644
index 0000000000000000000000000000000000000000..9618e3983750d2462e6ef80762daa245e8a39b96
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/schedule-modifiers-1.f90
@@ -0,0 +1,63 @@
+! { dg-do compile }
+! { dg-options "-fopenmp" }
+
+subroutine foo
+  integer :: i
+  !$omp do simd schedule (simd, simd: static, 5)
+  do i = 0, 64
+  end do
+  !$omp do simd schedule (monotonic, simd: static)
+  do i = 0, 64
+  end do
+  !$omp do simd schedule (simd , monotonic : static, 6)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic, monotonic : static, 7)
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic, nonmonotonic : dynamic)
+  do i = 0, 64
+  end do
+  !$omp do simd schedule (nonmonotonic , simd : dynamic, 3)
+  do i = 0, 64
+  end do
+  !$omp do simd schedule (nonmonotonic,simd:guided,4)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic: static, 2)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic : static)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic : dynamic)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic : dynamic, 3)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic : guided)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic : guided, 7)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic : runtime)
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic : auto)
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic : dynamic)
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic : dynamic, 3)
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic : guided)
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic : guided, 7)
+  do i = 0, 64
+  end do
+end subroutine foo
diff --git a/gcc/testsuite/gfortran.dg/gomp/schedule-modifiers-2.f90 b/gcc/testsuite/gfortran.dg/gomp/schedule-modifiers-2.f90
new file mode 100644
index 0000000000000000000000000000000000000000..0be53cc71a5d339dbb2c10e34ff6f9b739e11c17
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/schedule-modifiers-2.f90
@@ -0,0 +1,44 @@
+! { dg-do compile }
+! { dg-options "-fopenmp" }
+
+subroutine foo
+  integer :: i
+  !$omp do schedule (nonmonotonic: static, 2)	! { dg-error "NONMONOTONIC modifier specified for STATIC schedule kind" }
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic : static)	! { dg-error "NONMONOTONIC modifier specified for STATIC schedule kind" }
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic : runtime)	! { dg-error "NONMONOTONIC modifier specified for RUNTIME schedule kind" }
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic : auto)	! { dg-error "NONMONOTONIC modifier specified for AUTO schedule kind" }
+  do i = 0, 64
+  end do
+  !$omp do schedule (nonmonotonic : dynamic) ordered	! { dg-error "NONMONOTONIC schedule modifier specified with ORDERED clause" }
+  do i = 0, 64
+    !$omp ordered
+    !$omp end ordered
+  end do
+  !$omp do ordered schedule(nonmonotonic : dynamic, 5)	! { dg-error "NONMONOTONIC schedule modifier specified with ORDERED clause" }
+  do i = 0, 64
+    !$omp ordered
+    !$omp end ordered
+  end do
+  !$omp do schedule (nonmonotonic : guided) ordered(1)	! { dg-error "NONMONOTONIC schedule modifier specified with ORDERED clause" }
+  do i = 0, 64
+    !$omp ordered depend(sink: i - 1)
+    !$omp ordered depend(source)
+  end do
+  !$omp do ordered(1) schedule(nonmonotonic : guided, 2)	! { dg-error "NONMONOTONIC schedule modifier specified with ORDERED clause" }
+  do i = 0, 64
+    !$omp ordered depend(source)
+    !$ordered depend(sink: i - 1)
+  end do
+  !$omp do schedule (nonmonotonic , monotonic : dynamic)	! { dg-error "Both MONOTONIC and NONMONOTONIC schedule modifiers specified" }
+  do i = 0, 64
+  end do
+  !$omp do schedule (monotonic,nonmonotonic:dynamic)	! { dg-error "Both MONOTONIC and NONMONOTONIC schedule modifiers specified" }
+  do i = 0, 64
+  end do
+end subroutine foo