mirror of
https://github.com/github/semantic.git
synced 2024-12-22 22:31:36 +03:00
Revert "Constrain record fields to be Typeable."
This reverts commit 95fc1cb0ad4c7546450007b09fd690b4c84de1ce.
This commit is contained in:
parent
a34f9ae3a4
commit
995c839f3f
@ -14,13 +14,13 @@ import Test.QuickCheck
|
||||
-- | This is heavily inspired by Aaron Levin’s [Extensible Effects in the van Laarhoven Free Monad](http://aaronlevin.ca/post/136494428283/extensible-effects-in-the-van-laarhoven-free-monad).
|
||||
data Record :: [*] -> * where
|
||||
RNil :: Record '[]
|
||||
RCons :: Typeable h => h -> Record t -> Record (h ': t)
|
||||
RCons :: h -> Record t -> Record (h ': t)
|
||||
deriving Typeable
|
||||
|
||||
infixr 0 .:
|
||||
|
||||
-- | Infix synonym for `RCons`: `a .: b .: RNil == RCons a (RCons b RNil)`.
|
||||
(.:) :: Typeable h => h -> Record t -> Record (h ': t)
|
||||
(.:) :: h -> Record t -> Record (h ': t)
|
||||
(.:) = RCons
|
||||
|
||||
|
||||
@ -67,7 +67,7 @@ instance Ord (Record '[]) where
|
||||
_ `compare` _ = EQ
|
||||
|
||||
|
||||
instance (Typeable field, Arbitrary field, Arbitrary (Record fields)) => Arbitrary (Record (field ': fields)) where
|
||||
instance (Arbitrary field, Arbitrary (Record fields)) => Arbitrary (Record (field ': fields)) where
|
||||
arbitrary = RCons <$> arbitrary <*> arbitrary
|
||||
|
||||
shrink (RCons h t) = RCons <$> shrink h <*> shrink t
|
||||
|
@ -118,11 +118,11 @@ readAndTranscodeFile path = do
|
||||
type TermDecorator f fields field = CofreeF f (Record fields) (Record (field ': fields)) -> field
|
||||
|
||||
-- | Decorate the 'Term's produced by a 'Parser' using a function to compute the annotation values at every node.
|
||||
decorateParser :: (Typeable field, Functor f) => TermDecorator f fields field -> Parser f (Record fields) -> Parser f (Record (field ': fields))
|
||||
decorateParser :: Functor f => TermDecorator f fields field -> Parser f (Record fields) -> Parser f (Record (field ': fields))
|
||||
decorateParser decorator = (fmap (decorateTerm decorator) .)
|
||||
|
||||
-- | Decorate a 'Term' using a function to compute the annotation values at every node.
|
||||
decorateTerm :: (Typeable field, Functor f) => TermDecorator f fields field -> Cofree f (Record fields) -> Cofree f (Record (field ': fields))
|
||||
decorateTerm :: Functor f => TermDecorator f fields field -> Cofree f (Record fields) -> Cofree f (Record (field ': fields))
|
||||
decorateTerm decorator = cata $ \ c -> cofree ((decorator (extract <$> c) .: headF c) :< tailF c)
|
||||
|
||||
compareCategoryEq :: HasField fields Category => Term leaf (Record fields) -> Term leaf (Record fields) -> Bool
|
||||
|
Loading…
Reference in New Issue
Block a user