Try fixing compile error on older ghcs.

See https://github.com/jgm/gitit/runs/3308381697
This commit is contained in:
John MacFarlane 2021-08-11 23:14:17 -07:00
parent 073895c340
commit ec34497bc1

View file

@ -7,6 +7,9 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{- |
Module : Text.Pandoc.Readers.Odt.ContentReader
Copyright : Copyright (C) 2015 Martin Linnemann
@ -507,7 +510,8 @@ type InlineMatcher = ElementMatcher Inlines
type BlockMatcher = ElementMatcher Blocks
newtype FirstMatch a = FirstMatch (Alt Maybe a)
deriving (Foldable, Monoid, Semigroup)
deriving (Monoid, Semigroup)
deriving instance Foldable FirstMatch
firstMatch :: a -> FirstMatch a
firstMatch = FirstMatch . Alt . Just