From 0c6f7f7eb94f80d3ed74a382af8a3294d070e740 Mon Sep 17 00:00:00 2001
From: Simon Jakobi <simon.jakobi@gmail.com>
Date: Thu, 30 May 2019 00:16:09 +0200
Subject: [PATCH] Implement (Functor.<$) for Array

---
 libraries/base/GHC/Arr.hs | 9 +++++++++
 1 file changed, 9 insertions(+)

diff --git a/libraries/base/GHC/Arr.hs b/libraries/base/GHC/Arr.hs
index cc0397ec07..730f2205b5 100644
--- a/libraries/base/GHC/Arr.hs
+++ b/libraries/base/GHC/Arr.hs
@@ -848,6 +848,15 @@ cmpIntArray arr1@(Array l1 u1 n1 _) arr2@(Array l2 u2 n2 _) =
 instance Functor (Array i) where
     fmap = amap
 
+    {-# INLINE (<$) #-}
+    x <$ Array l u n@(I# n#) _ =
+        -- Sadly we can't just use 'newSTArray' (with 'unsafeFreezeSTArray')
+        -- since that would require proof that the indices of the original array
+        -- are instances of 'Ix'.
+        runST $ ST $ \s1# ->
+            case newArray# n# x s1# of
+                (# s2#, marr# #) -> done l u n marr# s2#
+
 -- | @since 2.01
 instance (Ix i, Eq e) => Eq (Array i e) where
     (==) = eqArray
-- 
GitLab