Skip to content

Commit

Permalink
Fixed the PolyKinds-related test errors
Browse files Browse the repository at this point in the history
  • Loading branch information
blamario committed Oct 13, 2024
1 parent f5963a9 commit d0712bc
Show file tree
Hide file tree
Showing 3 changed files with 9 additions and 8 deletions.
6 changes: 3 additions & 3 deletions deep-transformations/src/Transformation/AG/Dimorphic.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# Language DeriveDataTypeable, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, RankNTypes,
{-# Language Haskell2010, DeriveDataTypeable, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, RankNTypes,
ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}

-- | A special case of an attribute grammar where every node has only a single inherited and a single synthesized
Expand Down Expand Up @@ -140,9 +140,9 @@ traverseDefaultWithAttributes :: forall t p q r a b g.
traverseDefaultWithAttributes t x rootInheritance = Full.traverse Feeder (t Full.<$> x) rootInheritance
{-# INLINE traverseDefaultWithAttributes #-}

data Feeder a b (f :: Type -> Type) = Feeder
data Feeder (a :: Type) (b :: Type) (f :: Type -> Type) = Feeder

type FeederDomain a b f = Compose ((->) a) (Compose ((,) (Atts a b)) f)
type FeederDomain (a :: Type) (b :: Type) f = Compose ((->) a) (Compose ((,) (Atts a b)) f)

instance Transformation (Feeder a b f) where
type Domain (Feeder a b f) = FeederDomain a b f
Expand Down
4 changes: 2 additions & 2 deletions deep-transformations/src/Transformation/Deep.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# Language DeriveDataTypeable, FlexibleInstances, KindSignatures, MultiParamTypeClasses, RankNTypes,
{-# Language Haskell2010, DeriveDataTypeable, FlexibleInstances, KindSignatures, MultiParamTypeClasses, RankNTypes,
StandaloneDeriving, TypeFamilies, TypeOperators, UndecidableInstances #-}

-- | Type classes 'Functor', 'Foldable', and 'Traversable' that correspond to the standard type classes of the same
Expand Down Expand Up @@ -40,7 +40,7 @@ newtype Only g (d :: Type -> Type) (s :: Type -> Type) =
Only {fromOnly :: s (g d d)}

-- | Compose a regular type constructor with a data type with two type constructor parameters
newtype Nest f g (d :: Type -> Type) (s :: Type -> Type) =
newtype Nest (f :: Type -> Type) g (d :: Type -> Type) (s :: Type -> Type) =
Nest {unNest :: f (g d s)}

-- | Like 'Data.Functor.Product.Product' for data types with two type constructor parameters
Expand Down
7 changes: 4 additions & 3 deletions deep-transformations/src/Transformation/Rank2.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module Transformation.Rank2 where

import Data.Functor.Compose (Compose(Compose))
import Data.Functor.Const (Const(Const))
import Data.Kind (Type)
import qualified Rank2
import Transformation (Transformation, Domain, Codomain)
import qualified Transformation
Expand All @@ -26,11 +27,11 @@ foldMap f = Deep.foldMap (Fold f)
traverse :: Deep.Traversable (Traversal p q m) g => (forall a. p a -> m (q a)) -> g p p -> m (g q q)
traverse f = Deep.traverse (Traversal f)

newtype Map p q = Map (forall x. p x -> q x)
newtype Map (p :: Type -> Type) (q :: Type -> Type) = Map (forall x. p x -> q x)

newtype Fold p m = Fold (forall x. p x -> m)
newtype Fold (p :: Type -> Type) m = Fold (forall x. p x -> m)

newtype Traversal p q m = Traversal (forall x. p x -> m (q x))
newtype Traversal (p :: Type -> Type) (q :: Type -> Type) m = Traversal (forall x. p x -> m (q x))

instance Transformation (Map p q) where
type Domain (Map p q) = p
Expand Down

0 comments on commit d0712bc

Please sign in to comment.