diff --git a/gcc/fortran/dump-parse-tree.c b/gcc/fortran/dump-parse-tree.c
index 71d0e7d00f53c0e3a20ffca2e19852e3d9c8c3c1..6e265f4520d4da75c526b29967c85f5c87f63c00 100644
--- a/gcc/fortran/dump-parse-tree.c
+++ b/gcc/fortran/dump-parse-tree.c
@@ -1595,6 +1595,7 @@ show_omp_clauses (gfc_omp_clauses *omp_clauses)
 	  case OMP_LIST_IS_DEVICE_PTR: type = "IS_DEVICE_PTR"; break;
 	  case OMP_LIST_USE_DEVICE_PTR: type = "USE_DEVICE_PTR"; break;
 	  case OMP_LIST_USE_DEVICE_ADDR: type = "USE_DEVICE_ADDR"; break;
+	  case OMP_LIST_NONTEMPORAL: type = "NONTEMPORAL"; break;
 	  default:
 	    gcc_unreachable ();
 	  }
diff --git a/gcc/fortran/gfortran.h b/gcc/fortran/gfortran.h
index 48b2ab14fdbb057e387579164f2aa830455409b6..559d3c6b8b833d25bf91e8107ffec408e40145b8 100644
--- a/gcc/fortran/gfortran.h
+++ b/gcc/fortran/gfortran.h
@@ -1276,6 +1276,7 @@ enum
   OMP_LIST_IS_DEVICE_PTR,
   OMP_LIST_USE_DEVICE_PTR,
   OMP_LIST_USE_DEVICE_ADDR,
+  OMP_LIST_NONTEMPORAL,
   OMP_LIST_NUM
 };
 
diff --git a/gcc/fortran/openmp.c b/gcc/fortran/openmp.c
index f402febc2113eb3c6f55383606d2d803312bf9ae..c44a2530b881a89ae8526c26c105f403f133440c 100644
--- a/gcc/fortran/openmp.c
+++ b/gcc/fortran/openmp.c
@@ -794,6 +794,7 @@ enum omp_mask1
   OMP_CLAUSE_IS_DEVICE_PTR,
   OMP_CLAUSE_LINK,
   OMP_CLAUSE_NOGROUP,
+  OMP_CLAUSE_NOTEMPORAL,
   OMP_CLAUSE_NUM_TASKS,
   OMP_CLAUSE_PRIORITY,
   OMP_CLAUSE_SIMD,
@@ -1510,6 +1511,11 @@ gfc_match_omp_clauses (gfc_omp_clauses **cp, const omp_mask mask,
 	      c->nogroup = needs_space = true;
 	      continue;
 	    }
+	  if ((mask & OMP_CLAUSE_NOTEMPORAL)
+	      && gfc_match_omp_variable_list ("nontemporal (",
+					      &c->lists[OMP_LIST_NONTEMPORAL],
+					      true) == MATCH_YES)
+	    continue;
 	  if ((mask & OMP_CLAUSE_NOTINBRANCH)
 	      && !c->notinbranch
 	      && !c->inbranch
@@ -2591,7 +2597,7 @@ cleanup:
   (omp_mask (OMP_CLAUSE_PRIVATE) | OMP_CLAUSE_LASTPRIVATE		\
    | OMP_CLAUSE_REDUCTION | OMP_CLAUSE_COLLAPSE | OMP_CLAUSE_SAFELEN	\
    | OMP_CLAUSE_LINEAR | OMP_CLAUSE_ALIGNED | OMP_CLAUSE_SIMDLEN	\
-   | OMP_CLAUSE_IF | OMP_CLAUSE_ORDER)
+   | OMP_CLAUSE_IF | OMP_CLAUSE_ORDER | OMP_CLAUSE_NOTEMPORAL)
 #define OMP_TASK_CLAUSES \
   (omp_mask (OMP_CLAUSE_PRIVATE) | OMP_CLAUSE_FIRSTPRIVATE		\
    | OMP_CLAUSE_SHARED | OMP_CLAUSE_IF | OMP_CLAUSE_DEFAULT		\
diff --git a/gcc/fortran/trans-openmp.c b/gcc/fortran/trans-openmp.c
index 7891a7e651b5a0ccea846b837978d182a910eac8..063d4c145e20f0ad022eb17f5ce771d4c3cf20f9 100644
--- a/gcc/fortran/trans-openmp.c
+++ b/gcc/fortran/trans-openmp.c
@@ -2290,6 +2290,9 @@ gfc_trans_omp_clauses (stmtblock_t *block, gfc_omp_clauses *clauses,
 	case OMP_LIST_IS_DEVICE_PTR:
 	  clause_code = OMP_CLAUSE_IS_DEVICE_PTR;
 	  goto add_clause;
+	case OMP_LIST_NONTEMPORAL:
+	  clause_code = OMP_CLAUSE_NONTEMPORAL;
+	  goto add_clause;
 
 	add_clause:
 	  omp_clauses
diff --git a/gcc/testsuite/gfortran.dg/gomp/nontemporal-1.f90 b/gcc/testsuite/gfortran.dg/gomp/nontemporal-1.f90
new file mode 100644
index 0000000000000000000000000000000000000000..21a94db0ba80ba1b95c4e2b72396cb9f82b17282
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/nontemporal-1.f90
@@ -0,0 +1,25 @@
+! { dg-do compile }
+! { dg-additional-options "-O2 -fdump-tree-original" }
+
+module m
+  integer :: a(:), b(1024), c(1024), d(1024)
+  allocatable :: a
+end module m
+
+subroutine foo
+  use m
+  implicit none
+  integer :: i
+  !$omp simd nontemporal (a, b)
+  do i = 1, 1024
+    a(i) = b(i) + c(i)
+  end do
+
+  !$omp simd nontemporal (d)
+  do i = 1, 1024
+    d(i) = 2 * c(i)
+  end do
+end subroutine foo
+
+! { dg-final { scan-tree-dump-times "#pragma omp simd linear\\(i:1\\) nontemporal\\(a\\) nontemporal\\(b\\)" 1 "original" } }
+! { dg-final { scan-tree-dump-times "#pragma omp simd linear\\(i:1\\) nontemporal\\(d\\)" 1 "original" } }
diff --git a/gcc/testsuite/gfortran.dg/gomp/nontemporal-2.f90 b/gcc/testsuite/gfortran.dg/gomp/nontemporal-2.f90
new file mode 100644
index 0000000000000000000000000000000000000000..c880bedb1e23d520a5960672a50a3d0a2d249171
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/nontemporal-2.f90
@@ -0,0 +1,26 @@
+! { dg-do compile }
+
+module m
+ integer, allocatable :: a(:), b(:), c(:), d(:)
+end module m
+
+subroutine foo
+  use m
+  implicit none
+  integer :: i
+
+  !$omp simd nontemporal (a, b) aligned (a, b, c)
+  do i = 1, ubound(a, dim=1)
+    a(i) = b(i) + c(i)
+  end do
+
+  !$omp simd nontemporal (d) nontemporal (d)	! { dg-error "'d' present on multiple clauses" }
+  do i = 1, ubound(d, dim=1)
+    d(i) = 2 * c(i)
+  end do
+
+  !$omp simd nontemporal (a, b, b)		! { dg-error "'b' present on multiple clauses" }
+  do i = 1, ubound(a, dim=1)
+    a(i) = a(i) + b(i) + c(i)
+  end do
+end subroutine foo