diff --git a/lambda-buffers-compiler/lambda-buffers-compiler.cabal b/lambda-buffers-compiler/lambda-buffers-compiler.cabal index 538654ff..df34ff31 100644 --- a/lambda-buffers-compiler/lambda-buffers-compiler.cabal +++ b/lambda-buffers-compiler/lambda-buffers-compiler.cabal @@ -37,6 +37,7 @@ common common-language DeriveLift DeriveTraversable DerivingStrategies + DerivingVia DoAndIfThenElse DuplicateRecordFields EmptyCase @@ -94,12 +95,15 @@ library build-depends: , containers >=0.6.5.1 , freer-simple >=1.2 + , generic-arbitrary , generic-lens >=2.2 , lambda-buffers-compiler-pb >=0.1.0.0 , mtl >=2.2 , parsec >=3.1 , prettyprinter >=1.7 , proto-lens >=0.7 + , QuickCheck >=2.14 + , quickcheck-instances >=0.3 , text >=1.2 exposed-modules: @@ -147,16 +151,17 @@ test-suite tests , lambda-buffers-compiler , lambda-buffers-compiler-pb >=0.1 , proto-lens >=0.7 + , QuickCheck >=2.14 , tasty >=1.4 , tasty-hunit >=0.10 + , tasty-quickcheck >=0.10 , text >=1.2 other-modules: Test.KindCheck - Test.Samples - Test.Samples.Proto.CompilerInput - Test.Samples.Proto.Helpers - Test.Samples.Proto.Module - Test.Samples.Proto.SourceInfo - Test.Samples.Proto.TyDef Test.TypeClassCheck + Test.Utils.CompilerInput + Test.Utils.Constructors + Test.Utils.Module + Test.Utils.SourceInfo + Test.Utils.TyDef diff --git a/lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Type.hs b/lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Type.hs index aee82765..201f855f 100644 --- a/lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Type.hs +++ b/lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Type.hs @@ -8,6 +8,7 @@ module LambdaBuffers.Compiler.KindCheck.Type ( import LambdaBuffers.Compiler.KindCheck.Variable (Variable (LocalRef)) import Prettyprinter (Doc, Pretty (pretty), parens, (<+>)) +import Test.QuickCheck (Arbitrary, Gen, arbitrary, oneof, sized) data Type = Var Variable @@ -32,3 +33,16 @@ instance Pretty Type where Var a -> pretty a App t1 t2 -> parens $ show' t1 <+> show' t2 Abs a t1 -> parens $ "λ" <> pretty a <> "." <> show' t1 + +instance Arbitrary Type where + arbitrary = sized f + where + f :: Integral a => a -> Gen Type + f n + | n <= 0 = Var <$> arbitrary + | otherwise = + oneof + [ Var <$> arbitrary + , App <$> f (n `div` 2) <*> f (n `div` 2) + , Abs <$> arbitrary <*> f (n - 1) + ] diff --git a/lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Variable.hs b/lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Variable.hs index b3eb39e5..45ad5f46 100644 --- a/lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Variable.hs +++ b/lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Variable.hs @@ -1,14 +1,19 @@ module LambdaBuffers.Compiler.KindCheck.Variable (Variable (LocalRef, ForeignRef), Atom) where import Data.Text (Text) +import GHC.Generics (Generic) import Prettyprinter (Pretty (pretty), concatWith) +import Test.QuickCheck (Arbitrary) +import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary (GenericArbitrary)) +import Test.QuickCheck.Instances.Text () type Atom = Text data Variable = LocalRef Text | ForeignRef [Text] Text - deriving stock (Eq, Ord, Show) + deriving stock (Eq, Ord, Show, Generic) + deriving (Arbitrary) via GenericArbitrary Variable instance Pretty Variable where pretty = \case diff --git a/lambda-buffers-compiler/src/LambdaBuffers/Compiler/ProtoCompat/Types.hs b/lambda-buffers-compiler/src/LambdaBuffers/Compiler/ProtoCompat/Types.hs index d00992fa..2373e696 100644 --- a/lambda-buffers-compiler/src/LambdaBuffers/Compiler/ProtoCompat/Types.hs +++ b/lambda-buffers-compiler/src/LambdaBuffers/Compiler/ProtoCompat/Types.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DuplicateRecordFields #-} +{-# OPTIONS_GHC -Wno-orphans #-} {-# OPTIONS_GHC -Wno-redundant-constraints #-} +{-# OPTIONS_GHC -Wno-unused-imports #-} module LambdaBuffers.Compiler.ProtoCompat.Types ( ClassDef (..), @@ -46,143 +48,156 @@ module LambdaBuffers.Compiler.ProtoCompat.Types ( module VARS, ) where +-- for NonEmpty import Control.Exception (Exception) -import Data.List.NonEmpty (NonEmpty) +import Data.List.NonEmpty (NonEmpty ((:|))) import Data.Text (Text) import GHC.Generics (Generic) import LambdaBuffers.Compiler.KindCheck.Variable as VARS (Atom, Variable) +import Test.QuickCheck (Gen, oneof, resize, sized) +import Test.QuickCheck.Arbitrary.Generic (Arbitrary (arbitrary), GenericArbitrary (GenericArbitrary)) +import Test.QuickCheck.Instances.Semigroup () data SourceInfo = SourceInfo {file :: Text, posFrom :: SourcePosition, posTo :: SourcePosition} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary SourceInfo data SourcePosition = SourcePosition {column :: Int, row :: Int} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary SourcePosition --- NOTE(gnumonik): I need a "generic name" type for my template haskell, this shouldn't be used anywhere outside of that +{- | NOTE(gnumonik): I need a "generic name" type for my template haskell, this + shouldn't be used anywhere outside of that +-} data LBName = LBName {name :: Text, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary LBName data TyName = TyName {name :: Text, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyName data ConstrName = ConstrName {name :: Text, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary ConstrName data ModuleName = ModuleName {parts :: [ModuleNamePart], sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary ModuleName data ModuleNamePart = ModuleNamePart {name :: Text, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary ModuleNamePart data VarName = VarName {name :: Text, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary VarName data FieldName = FieldName {name :: Text, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary FieldName data ClassName = ClassName {name :: Text, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary ClassName newtype Kind = Kind {kind :: KindType} deriving stock (Show, Eq, Ord, Generic) -data KindType - = KindRef KindRefType - | KindArrow Kind Kind +instance Arbitrary Kind where + arbitrary = sized fn + where + fn n = Kind <$> resize n arbitrary + +data KindType = KindRef KindRefType | KindArrow Kind Kind deriving stock (Show, Eq, Ord, Generic) -data KindRefType - = KUnspecified - | KType +instance Arbitrary KindType where + arbitrary = sized fn + where + fn n + | n <= 0 = KindRef <$> arbitrary + | otherwise = KindArrow <$> resize (n `div` 2) arbitrary <*> resize (n `div` 2) arbitrary + +data KindRefType = KUnspecified | KType deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary KindRefType data TyVar = TyVar {varName :: VarName, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyVar -data Ty - = TyVarI TyVar - | TyAppI TyApp - | TyRefI TyRef +data Ty = TyVarI TyVar | TyAppI TyApp | TyRefI TyRef deriving stock (Show, Eq, Ord, Generic) -data TyApp = TyApp - { tyFunc :: Ty - , tyArgs :: NonEmpty Ty - , sourceInfo :: SourceInfo - } +instance Arbitrary Ty where + arbitrary = sized fn + where + fn :: (Num a, Ord a) => a -> Gen Ty + fn n + | n <= 0 = TyRefI <$> arbitrary + | otherwise = + oneof + [ TyVarI <$> arbitrary + , TyAppI <$> arbitrary + , TyRefI <$> arbitrary + ] + +data TyApp = TyApp {tyFunc :: Ty, tyArgs :: NonEmpty Ty, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyApp data ForeignRef = ForeignRef {tyName :: TyName, moduleName :: ModuleName, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary ForeignRef data LocalRef = LocalRef {tyName :: TyName, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary LocalRef -data TyRef - = LocalI LocalRef - | ForeignI ForeignRef +data TyRef = LocalI LocalRef | ForeignI ForeignRef deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyRef -data TyDef = TyDef - { tyName :: TyName - , tyAbs :: TyAbs - , sourceInfo :: SourceInfo - } +data TyDef = TyDef {tyName :: TyName, tyAbs :: TyAbs, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyDef -data TyAbs = TyAbs - { tyArgs :: [TyArg] - , tyBody :: TyBody - , sourceInfo :: SourceInfo - } +data TyAbs = TyAbs {tyArgs :: [TyArg], tyBody :: TyBody, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyAbs -data TyArg = TyArg - { argName :: VarName - , argKind :: Kind - , sourceInfo :: SourceInfo - } +data TyArg = TyArg {argName :: VarName, argKind :: Kind, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyArg -data TyBody - = OpaqueI SourceInfo - | SumI Sum +data TyBody = OpaqueI SourceInfo | SumI Sum deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyBody -data Constructor = Constructor - { constrName :: ConstrName - , product :: Product - } +data Constructor = Constructor {constrName :: ConstrName, product :: Product} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary Constructor -data Sum = Sum - { constructors :: NonEmpty Constructor - , sourceInfo :: SourceInfo - } +data Sum = Sum {constructors :: NonEmpty Constructor, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary Sum -data Field = Field - { fieldName :: FieldName - , fieldTy :: Ty - } +data Field = Field {fieldName :: FieldName, fieldTy :: Ty} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary Field -data Record = Record - { fields :: NonEmpty Field - , sourceInfo :: SourceInfo - } +data Record = Record {fields :: NonEmpty Field, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary Record -data Tuple = Tuple - { fields :: [Ty] - , sourceInfo :: SourceInfo - } +data Tuple = Tuple {fields :: [Ty], sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary Tuple -data Product - = RecordI Record - | TupleI Tuple +data Product = RecordI Record | TupleI Tuple deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary Product data ForeignClassRef = ForeignClassRef { className :: ClassName @@ -190,14 +205,17 @@ data ForeignClassRef = ForeignClassRef , sourceInfo :: SourceInfo } deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary ForeignClassRef data LocalClassRef = LocalClassRef {className :: ClassName, sourceInfo :: SourceInfo} deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary LocalClassRef data TyClassRef = LocalCI LocalClassRef | ForeignCI ForeignClassRef deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary TyClassRef data ClassDef = ClassDef { className :: ClassName @@ -207,6 +225,7 @@ data ClassDef = ClassDef , sourceInfo :: SourceInfo } deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary ClassDef data InstanceClause = InstanceClause { classRef :: TyClassRef @@ -216,12 +235,23 @@ data InstanceClause = InstanceClause } deriving stock (Show, Eq, Ord, Generic) +instance Arbitrary InstanceClause where + arbitrary = sized fn + where + fn n = + InstanceClause + <$> resize n arbitrary + <*> resize n arbitrary + <*> resize n arbitrary + <*> resize n arbitrary + data Constraint = Constraint { classRef :: TyClassRef , argument :: Ty , sourceInfo :: SourceInfo } deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary Constraint data Module = Module { moduleName :: ModuleName @@ -233,10 +263,45 @@ data Module = Module } deriving stock (Show, Eq, Ord, Generic) +instance Arbitrary Module where + arbitrary = sized fn + where + fn n = + Module + <$> resize n arbitrary + <*> resize n arbitrary + <*> resize n arbitrary + <*> resize n arbitrary + <*> resize n arbitrary + <*> resize n arbitrary + +data InferenceErr + = UnboundTermErr Text + | ImpossibleErr Text + | UnificationErr Text + | RecursiveSubstitutionErr Text + deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary InferenceErr + +instance Exception InferenceErr + +data KindCheckErr + = InconsistentTypeErr TyDef + | InferenceFailure TyDef InferenceErr + deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary KindCheckErr + +instance Exception KindCheckErr + newtype CompilerInput = CompilerInput {modules :: [Module]} deriving stock (Show, Eq, Ord, Generic) deriving newtype (Monoid, Semigroup) +instance Arbitrary CompilerInput where + arbitrary = sized fn + where + fn n = CompilerInput <$> resize n arbitrary + data KindCheckError = -- | The following term is unbound in the following type definition. UnboundTermError TyName VarName @@ -247,14 +312,17 @@ data KindCheckError | -- | The following type has the wrong. InconsistentTypeError TyName Kind Kind deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary KindCheckError instance Exception KindCheckError data CompilerError = CompKindCheckError KindCheckError | InternalError Text deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary CompilerError data CompilerResult = CompilerResult deriving stock (Show, Eq, Ord, Generic) + deriving (Arbitrary) via GenericArbitrary CompilerResult type CompilerOutput = Either CompilerError CompilerResult diff --git a/lambda-buffers-compiler/test/Test/KindCheck.hs b/lambda-buffers-compiler/test/Test/KindCheck.hs index f56c07bd..5708491a 100644 --- a/lambda-buffers-compiler/test/Test/KindCheck.hs +++ b/lambda-buffers-compiler/test/Test/KindCheck.hs @@ -1,5 +1,6 @@ module Test.KindCheck (test) where +import Data.Bifunctor (Bifunctor (bimap)) import Data.List.NonEmpty (NonEmpty ((:|)), cons) import Data.Text (Text) import LambdaBuffers.Compiler.KindCheck ( @@ -14,21 +15,34 @@ import LambdaBuffers.Compiler.KindCheck.Variable ( import LambdaBuffers.Compiler.ProtoCompat.Types qualified as P ( CompilerInput (CompilerInput), ) -import Test.Samples.Proto.CompilerInput ( - compilerInput'incoherent, - compilerInput'maybe, +import Test.QuickCheck ( + Arbitrary (arbitrary, shrink), + Property, + forAll, + forAllShrink, + resize, + shuffle, + (===), ) import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (assertBool, testCase, (@?=)) +import Test.Tasty.QuickCheck (testProperty) +import Test.Utils.CompilerInput ( + compilerInput'incoherent, + compilerInput'maybe, + ) + +-------------------------------------------------------------------------------- +-- Top Level tests test :: TestTree -test = testGroup "Compiler tests" [testCheck, testFolds] +test = testGroup "Compiler tests" [testCheck, testFolds, testRefl] -------------------------------------------------------------------------------- -- Module tests testCheck :: TestTree -testCheck = testGroup "KindChecker Tests" [trivialKCTest, kcTestMaybe, kcTestFailing] +testCheck = testGroup "KindChecker Tests" [trivialKCTest, kcTestMaybe, kcTestFailing, kcTestOrdering] trivialKCTest :: TestTree trivialKCTest = @@ -46,6 +60,27 @@ kcTestFailing = assertBool "Test should have failed." $ check_ compilerInput'incoherent /= Right () +{- | TyDef order does not matter when kind checking. + + We're not interested in the failure error as there might be more than two + errors in a module - and it is non-determistic which one is first. But it is + deterministic if the property holds for the whole CompilerInput. Therefore we + only track if given the input - the fails or succeeds. +-} +kcTestOrdering :: TestTree +kcTestOrdering = + testProperty "Module order inside the CompilerInput does not matter." $ + forAllShrink (resize 5 genModuleIn2Layouts) shrink $ + \(l, r) -> eitherFailOrPass (check_ l) == eitherFailOrPass (check_ r) + where + genModuleIn2Layouts = do + mods <- arbitrary + shuffledMods <- shuffle mods + pure (P.CompilerInput mods, P.CompilerInput shuffledMods) + + eitherFailOrPass :: forall {a} {c}. Either a c -> Either () () + eitherFailOrPass = bimap (const ()) (const ()) + -------------------------------------------------------------------------------- -- Fold tests @@ -53,7 +88,7 @@ testFolds :: TestTree testFolds = testGroup "Test Folds" - [ testGroup "Test Product Folds." [testFoldProd1, testFoldProd2, testFoldProd3] + [ testGroup "Test Product Folds." [testFoldProd1, testFoldProd2, testFoldProd3, testPProdFoldTotal] , testGroup "Test Sum Folds." [testSumFold1, testSumFold2, testSumFold3] ] @@ -79,6 +114,12 @@ testFoldProd3 = (App (lVar "Π") (lVar "c")) (App (App (lVar "Π") (lVar "b")) (lVar "a")) +testPProdFoldTotal :: TestTree +testPProdFoldTotal = + testProperty "ProductFold is total." $ + forAll arbitrary $ + \ts -> foldWithProduct ts === foldWithProduct ts + -- | [ a ] -> a testSumFold1 :: TestTree testSumFold1 = @@ -104,3 +145,10 @@ testSumFold3 = -- | TyDef to Kind Canonical representation - sums not folded - therefore we get constructor granularity. Might use in a different implementation for more granular errors. lVar :: Text -> Type lVar = Var . LocalRef + +-- Property Tests +testRefl :: TestTree +testRefl = testProperty "Refl" reflTerm + where + reflTerm :: Property + reflTerm = forAllShrink (arbitrary @Int) shrink (\a -> a == a) diff --git a/lambda-buffers-compiler/test/Test/Samples.hs b/lambda-buffers-compiler/test/Test/Samples.hs deleted file mode 100644 index e0660f66..00000000 --- a/lambda-buffers-compiler/test/Test/Samples.hs +++ /dev/null @@ -1,7 +0,0 @@ -{-# OPTIONS_GHC -Wno-missing-import-lists #-} - -module Test.Samples (module M) where - -import Test.Samples.Proto.CompilerInput as M -import Test.Samples.Proto.Module as M -import Test.Samples.Proto.SourceInfo as M diff --git a/lambda-buffers-compiler/test/Test/Samples/Proto/CompilerInput.hs b/lambda-buffers-compiler/test/Test/Utils/CompilerInput.hs similarity index 72% rename from lambda-buffers-compiler/test/Test/Samples/Proto/CompilerInput.hs rename to lambda-buffers-compiler/test/Test/Utils/CompilerInput.hs index d65d829e..eba09124 100644 --- a/lambda-buffers-compiler/test/Test/Samples/Proto/CompilerInput.hs +++ b/lambda-buffers-compiler/test/Test/Utils/CompilerInput.hs @@ -1,8 +1,8 @@ -module Test.Samples.Proto.CompilerInput (compilerInput'incoherent, compilerInput'maybe) where +module Test.Utils.CompilerInput (compilerInput'incoherent, compilerInput'maybe) where import Control.Lens ((&), (.~)) import LambdaBuffers.Compiler.ProtoCompat qualified as P -import Test.Samples.Proto.Module (module'incoherent, module'maybe) +import Test.Utils.Module (module'incoherent, module'maybe) -- | Compiler Input containing 1 module with 1 definition - Maybe. compilerInput'maybe :: P.CompilerInput diff --git a/lambda-buffers-compiler/test/Test/Samples/Proto/Helpers.hs b/lambda-buffers-compiler/test/Test/Utils/Constructors.hs similarity index 95% rename from lambda-buffers-compiler/test/Test/Samples/Proto/Helpers.hs rename to lambda-buffers-compiler/test/Test/Utils/Constructors.hs index 50c74693..936481b4 100644 --- a/lambda-buffers-compiler/test/Test/Samples/Proto/Helpers.hs +++ b/lambda-buffers-compiler/test/Test/Utils/Constructors.hs @@ -1,4 +1,4 @@ -module Test.Samples.Proto.Helpers ( +module Test.Utils.Constructors ( _tyName, _varName, _tyVar, @@ -17,7 +17,7 @@ module Test.Samples.Proto.Helpers ( import Data.List.NonEmpty (fromList) import Data.Text (Text) import LambdaBuffers.Compiler.ProtoCompat qualified as P -import Test.Samples.Proto.SourceInfo (sourceInfo'empty) +import Test.Utils.SourceInfo (sourceInfo'empty) _tyName :: Text -> P.TyName _tyName x = P.TyName x sourceInfo'empty diff --git a/lambda-buffers-compiler/test/Test/Samples/Proto/Module.hs b/lambda-buffers-compiler/test/Test/Utils/Module.hs similarity index 79% rename from lambda-buffers-compiler/test/Test/Samples/Proto/Module.hs rename to lambda-buffers-compiler/test/Test/Utils/Module.hs index c533ac02..02148b8f 100644 --- a/lambda-buffers-compiler/test/Test/Samples/Proto/Module.hs +++ b/lambda-buffers-compiler/test/Test/Utils/Module.hs @@ -1,9 +1,9 @@ -module Test.Samples.Proto.Module (module'maybe, module'incoherent) where +module Test.Utils.Module (module'maybe, module'incoherent) where import Control.Lens ((%~), (&)) import LambdaBuffers.Compiler.ProtoCompat qualified as P -import Test.Samples.Proto.SourceInfo (sourceInfo'empty) -import Test.Samples.Proto.TyDef (tyDef'incoherent, tyDef'maybe) +import Test.Utils.SourceInfo (sourceInfo'empty) +import Test.Utils.TyDef (tyDef'incoherent, tyDef'maybe) module'maybe :: P.Module module'maybe = diff --git a/lambda-buffers-compiler/test/Test/Samples/Proto/SourceInfo.hs b/lambda-buffers-compiler/test/Test/Utils/SourceInfo.hs similarity index 76% rename from lambda-buffers-compiler/test/Test/Samples/Proto/SourceInfo.hs rename to lambda-buffers-compiler/test/Test/Utils/SourceInfo.hs index 03fe0da9..cb04608b 100644 --- a/lambda-buffers-compiler/test/Test/Samples/Proto/SourceInfo.hs +++ b/lambda-buffers-compiler/test/Test/Utils/SourceInfo.hs @@ -1,4 +1,4 @@ -module Test.Samples.Proto.SourceInfo (sourceInfo'empty) where +module Test.Utils.SourceInfo (sourceInfo'empty) where import LambdaBuffers.Compiler.ProtoCompat qualified as P diff --git a/lambda-buffers-compiler/test/Test/Samples/Proto/TyDef.hs b/lambda-buffers-compiler/test/Test/Utils/TyDef.hs similarity index 84% rename from lambda-buffers-compiler/test/Test/Samples/Proto/TyDef.hs rename to lambda-buffers-compiler/test/Test/Utils/TyDef.hs index 9866f758..e6603f38 100644 --- a/lambda-buffers-compiler/test/Test/Samples/Proto/TyDef.hs +++ b/lambda-buffers-compiler/test/Test/Utils/TyDef.hs @@ -1,7 +1,7 @@ -module Test.Samples.Proto.TyDef (tyDef'maybe, tyDef'incoherent) where +module Test.Utils.TyDef (tyDef'maybe, tyDef'incoherent) where import LambdaBuffers.Compiler.ProtoCompat qualified as P -import Test.Samples.Proto.Helpers ( +import Test.Utils.Constructors ( _TupleI, _TyAbs, _TyDef,