Skip to content

Commit

Permalink
Fix ancient GHC
Browse files Browse the repository at this point in the history
  • Loading branch information
mniip committed Feb 9, 2024
1 parent 6c8814c commit a7889a3
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 3 deletions.
3 changes: 1 addition & 2 deletions semialign/src/Data/Crosswalk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,13 +8,12 @@ module Data.Crosswalk (
Bicrosswalk (..),
) where

import Control.Applicative (Applicative (pure, (<*>)), (<$>))
import Control.Applicative (Applicative (pure, (<*>)), (<$>), Const(..))
import Control.Monad.Trans.Maybe (MaybeT (..))
import Data.Bifoldable (Bifoldable (..))
import Data.Bifunctor (Bifunctor (..))
import Data.Foldable (Foldable (..))
import Data.Functor.Compose (Compose (..))
import Data.Functor.Const (Const (..))
import Data.Functor.Identity (Identity (..))
import Data.Functor.Sum (Sum (..))
import Data.Functor.These (These1 (..))
Expand Down
2 changes: 1 addition & 1 deletion these-tests/test/Tests/Crosswalk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,10 +6,10 @@ module Tests.Crosswalk (crosswalkProps) where
import Prelude ()
import Prelude.Compat

import Control.Applicative (Const)
import Control.Monad.Trans.Instances ()
import Control.Monad.Trans.Maybe (MaybeT)
import Data.Functor.Compose (Compose (..))
import Data.Functor.Const (Const)
import Data.Functor.Identity (Identity (..))
import Data.Functor.Sum (Sum)
import Data.Functor.These (These1)
Expand Down
18 changes: 18 additions & 0 deletions these-tests/test/Tests/Orphans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,17 +4,35 @@
module Tests.Orphans where

#if !(MIN_VERSION_base(4,7,0))
import Control.Monad.Trans.Maybe (MaybeT)
import Data.Typeable.Internal
import Data.Functor.Compose (Compose)
import Data.Functor.Product (Product)
import Data.Functor.Sum (Sum)
import Data.Functor.These (These1)

instance (Typeable1 f, Typeable1 g) => Typeable1 (Product f g) where
typeOf1 _ = mkTyConApp
(mkTyCon3 "transformers" "Data.Functor.Product" "Product")
[typeOf1 (undefined :: f ()), typeOf1 (undefined :: f ())]

instance (Typeable1 f, Typeable1 g) => Typeable1 (Sum f g) where
typeOf1 _ = mkTyConApp
(mkTyCon3 "transformers" "Data.Functor.Sum" "Sum")
[typeOf1 (undefined :: f ()), typeOf1 (undefined :: f ())]

instance (Typeable1 f, Typeable1 g) => Typeable1 (These1 f g) where
typeOf1 _ = mkTyConApp
(mkTyCon3 "these" "Data.Functor.These" "These1")
[typeOf1 (undefined :: f ()), typeOf1 (undefined :: f ())]

instance (Typeable1 f, Typeable1 g) => Typeable1 (Compose f g) where
typeOf1 _ = mkTyConApp
(mkTyCon3 "transformers" "Data.Functor.Compose" "Compose")
[typeOf1 (undefined :: f ()), typeOf1 (undefined :: f ())]

instance Typeable1 f => Typeable1 (MaybeT f) where
typeOf1 _ = mkTyConApp
(mkTyCon3 "transformers" "Control.Monad.Trans.Maybe" "MaybeT")
[typeOf1 (undefined :: f ())]
#endif

0 comments on commit a7889a3

Please sign in to comment.