diff --git a/tests/MA/Functors/MonoidValuedSpec.hs b/tests/MA/Functors/MonoidValuedSpec.hs index 6f2c4579fc3b3747163907a5a80ff5f8e5849db8..42b2d450dd0109c8cfafdcedee1f9a4b17ffa78a 100644 --- a/tests/MA/Functors/MonoidValuedSpec.hs +++ b/tests/MA/Functors/MonoidValuedSpec.hs @@ -1,5 +1,6 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleContexts #-} + module MA.Functors.MonoidValuedSpec (spec) where import Test.Hspec @@ -166,74 +167,3 @@ maxRealRefineSpec = describe "maxReal refine" $ do encoding :: [h1] -> [(Int, l, Int)] -> Encoding l h1 encoding h1 es = Encoding.new (V.fromList h1) (V.fromList (map toEdge es)) where toEdge (from, lab, to) = Encoding.Edge from lab to - --- mkPoly :: [[Factor a]] -> Polynomial a --- mkPoly = --- Polynomial . Sum . NonEmpty.fromList . map (Product . NonEmpty.fromList) - --- type Suitable f = ( Functor f --- , ParseMorphism f --- , Show (Label f) --- , Show (H1 f) --- , Eq (Label f) --- , Eq (H1 f) --- , Typeable (Label f) --- , Typeable (H1 f) --- , Show1 f --- ) - --- data SomeFunctor a where --- SomeFunctor --- :: Suitable f --- => f a --- -> SomeFunctor a - --- deriving instance Functor SomeFunctor - --- instance Show1 SomeFunctor where --- liftShowsPrec f fl i (SomeFunctor inner) = liftShowsPrec f fl i inner - --- instance Eq1 SomeFunctor where --- liftEq f (SomeFunctor a) (SomeFunctor b) = liftEq f a b - --- data SomeLabel where --- SomeLabel --- :: forall l. (Show l, Eq l, Typeable l) --- => l --- -> SomeLabel - --- deriving instance Show SomeLabel - --- instance Eq SomeLabel where --- (SomeLabel (a :: ta)) == (SomeLabel (b :: tb)) = --- case eqTypeRep (typeRep @ta) (typeRep @tb) of --- Nothing -> False --- Just HRefl -> a == b - --- data SomeH1 where --- SomeH1 :: forall h. (Show h, Eq h, Typeable h) => h -> SomeH1 - --- deriving instance Show SomeH1 - --- instance Eq SomeH1 where --- (SomeH1 (a :: ta)) == (SomeH1 (b :: tb)) = --- case eqTypeRep (typeRep @ta) (typeRep @tb) of --- Nothing -> False --- Just HRefl -> a == b - --- type instance H1 SomeFunctor = SomeH1 --- type instance Label SomeFunctor = SomeLabel - --- instance ParseMorphism SomeFunctor where --- parseMorphismPoint (SomeFunctor f) = do --- convertOuter (parseMorphismPoint f) --- where --- convertOuter = --- fmap (\(h1, succs) -> (SomeH1 h1, fmap (_2 %~ SomeLabel) succs)) - --- someFunctor --- :: (Suitable f, Typeable f, ParseMorphism f) --- => FunctorDescription f --- -> FunctorDescription SomeFunctor --- someFunctor fd = --- fd { functorExprParser = transParser SomeFunctor (functorExprParser fd) }