diff --git a/libraries/base/src/Data/List/NonEmpty.hs b/libraries/base/src/Data/List/NonEmpty.hs
index b5c4cd5b4dad2b941437bc644da1a46a79de8bf6..7617fcde6ed5422d52e58121c6138c2ad798ecc3 100644
--- a/libraries/base/src/Data/List/NonEmpty.hs
+++ b/libraries/base/src/Data/List/NonEmpty.hs
@@ -78,6 +78,8 @@ module Data.List.NonEmpty (
    , groupBy1    -- :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
    , groupWith1     -- :: (Foldable f, Eq b) => (a -> b) -> f a -> NonEmpty (NonEmpty a)
    , groupAllWith1  -- :: (Foldable f, Ord b) => (a -> b) -> f a -> NonEmpty (NonEmpty a)
+   , permutations
+   , permutations1
    -- * Sublist predicates
    , isPrefixOf  -- :: Foldable f => f a -> NonEmpty a -> Bool
    -- * \"Set\" operations
@@ -441,6 +443,22 @@ groupWith1 f = groupBy1 ((==) `on` f)
 groupAllWith1 :: (Ord b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
 groupAllWith1 f = groupWith1 f . sortWith f
 
+-- | The 'permutations' function returns the list of all permutations of the argument.
+permutations            :: [a] -> NonEmpty [a]
+permutations xs0        =  xs0 :| perms xs0 []
+  where
+    perms []     _  = []
+    perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations is)
+      where interleave    xs     r = let (_,zs) = interleave' id xs r in zs
+            interleave' _ []     r = (ts, r)
+            interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:)) ys r
+                                     in  (y:us, f (t:y:us) : zs)
+
+-- | 'permutations1' operates like 'permutations', but uses the knowledge that its input is
+-- non-empty to produce output which every element is non-empty.
+permutations1 :: NonEmpty a -> NonEmpty (NonEmpty a)
+permutations1 xs = fromList <$> permutations (toList xs)
+
 -- | The 'isPrefixOf' function returns 'True' if the first argument is
 -- a prefix of the second.
 isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool