From 3cfcfacd728fec948d72e04bfcd64bbf97979280 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Thu, 12 Aug 2021 09:22:34 -0700
Subject: [PATCH] Use Prelude from base-compat for ghc 8.4 too.

We were having trouble building on ghc 8.4 because of
the lack of a Foldable instance for (Alt Maybe) in
base < 4.12.

Mystery: for some reason our builds were failing for gitit
but not in the pandoc CI.
---
 pandoc.cabal                                 | 2 +-
 src/Text/Pandoc/Readers/Odt/ContentReader.hs | 6 +-----
 2 files changed, 2 insertions(+), 6 deletions(-)

diff --git a/pandoc.cabal b/pandoc.cabal
index 81c3546e7..66ac50ce3 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -410,7 +410,7 @@ common common-options
                     -Wincomplete-record-updates
                     -Wnoncanonical-monad-instances
 
-  if impl(ghc < 8.4)
+  if impl(ghc < 8.6)
     hs-source-dirs:   prelude
     other-modules:    Prelude
     build-depends:    base-compat >= 0.9
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 734a6e116..5520d039f 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -7,9 +7,6 @@
 {-# LANGUAGE TupleSections     #-}
 {-# LANGUAGE ViewPatterns      #-}
 {-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE StandaloneDeriving #-}
-{-# LANGUAGE FlexibleInstances  #-}
-{-# LANGUAGE FlexibleContexts   #-}
 {- |
    Module      : Text.Pandoc.Readers.Odt.ContentReader
    Copyright   : Copyright (C) 2015 Martin Linnemann
@@ -510,8 +507,7 @@ type InlineMatcher = ElementMatcher Inlines
 type BlockMatcher  = ElementMatcher Blocks
 
 newtype FirstMatch a = FirstMatch (Alt Maybe a)
-  deriving (Monoid, Semigroup)
-deriving instance Foldable FirstMatch
+  deriving (Foldable, Monoid, Semigroup)
 
 firstMatch :: a -> FirstMatch a
 firstMatch = FirstMatch . Alt . Just