module Test.ParseMetadata (tests) where
import Control.Monad (when)
import Base.CompilerError
import Base.Positional
import Base.TrackedErrors
import Cli.CompileOptions
import Cli.Programs (VersionHash(..))
import Module.CompileMetadata
import Module.ParseMetadata
import System.FilePath
import Test.Common
import Types.Procedure
import Types.TypeCategory
import Types.TypeInstance
hugeCompileMetadata :: CompileMetadata
hugeCompileMetadata :: CompileMetadata
hugeCompileMetadata = CompileMetadata {
cmVersionHash :: VersionHash
cmVersionHash = FilePath -> VersionHash
VersionHash FilePath
"0123456789ABCDEFabcdef",
cmRoot :: FilePath
cmRoot = FilePath
"/home/project",
cmPath :: FilePath
cmPath = FilePath
"/home/project/special",
cmExtra :: [FilePath]
cmExtra = [
FilePath
"extra1",
FilePath
"extra2"
],
cmPublicNamespace :: Namespace
cmPublicNamespace = FilePath -> Namespace
StaticNamespace FilePath
"public_ABCDEF",
cmPrivateNamespace :: Namespace
cmPrivateNamespace = FilePath -> Namespace
StaticNamespace FilePath
"private_ABCDEF",
cmPublicDeps :: [FilePath]
cmPublicDeps = [
FilePath
"/home/project/public-dep1",
FilePath
"/home/project/public-dep2"
],
cmPrivateDeps :: [FilePath]
cmPrivateDeps = [
FilePath
"/home/project/private-dep1",
FilePath
"/home/project/private-dep2"
],
cmPublicCategories :: [CategoryName]
cmPublicCategories = [
FilePath -> CategoryName
CategoryName FilePath
"MyCategory",
FilePath -> CategoryName
CategoryName FilePath
"MyOtherCategory"
],
cmPrivateCategories :: [CategoryName]
cmPrivateCategories = [
FilePath -> CategoryName
CategoryName FilePath
"PrivateCategory",
FilePath -> CategoryName
CategoryName FilePath
"PrivateOtherCategory"
],
cmPublicSubdirs :: [FilePath]
cmPublicSubdirs = [
FilePath
"/home/project/special/subdir1",
FilePath
"/home/project/special/subdir2"
],
cmPrivateSubdirs :: [FilePath]
cmPrivateSubdirs = [
FilePath
"/home/project/special/subdir1",
FilePath
"/home/project/special/subdir2"
],
cmPublicFiles :: [FilePath]
cmPublicFiles = [
FilePath
"/home/project/special/category1.0rp",
FilePath
"/home/project/special/category2.0rp"
],
cmPrivateFiles :: [FilePath]
cmPrivateFiles = [
FilePath
"/home/project/special/category1.0rx",
FilePath
"/home/project/special/category2.0rx"
],
cmTestFiles :: [FilePath]
cmTestFiles = [
FilePath
"/home/project/special/category1.0rt",
FilePath
"/home/project/special/category2.0rt"
],
cmHxxFiles :: [FilePath]
cmHxxFiles = [
FilePath
"/home/project/special/category1.hpp",
FilePath
"/home/project/special/category2.hpp"
],
cmCxxFiles :: [FilePath]
cmCxxFiles = [
FilePath
"/home/project/special/category1.cpp",
FilePath
"/home/project/special/category2.cpp"
],
cmBinaries :: [FilePath]
cmBinaries = [
FilePath
"/home/project/special/binary1",
FilePath
"/home/project/special/binary2"
],
cmLibraries :: [FilePath]
cmLibraries = [
FilePath
"/home/project/special/library1",
FilePath
"/home/project/special/library2"
],
cmLinkFlags :: [FilePath]
cmLinkFlags = [
FilePath
"-lm",
FilePath
"-ldl"
],
cmObjectFiles :: [ObjectFile]
cmObjectFiles = [
CategoryObjectFile {
cofCategory :: CategoryIdentifier
cofCategory = CategoryIdentifier {
ciPath :: FilePath
ciPath = FilePath
"/home/project/special",
ciCategory :: CategoryName
ciCategory = FilePath -> CategoryName
CategoryName FilePath
"SpecialCategory",
ciNamespace :: Namespace
ciNamespace = FilePath -> Namespace
StaticNamespace FilePath
"public_ABCDEF"
},
cofRequires :: [CategoryIdentifier]
cofRequires = [
CategoryIdentifier {
ciPath :: FilePath
ciPath = FilePath
"/home/project/private-dep1",
ciCategory :: CategoryName
ciCategory = FilePath -> CategoryName
CategoryName FilePath
"PrivateCategory",
ciNamespace :: Namespace
ciNamespace = Namespace
NoNamespace
},
UnresolvedCategory {
ucCategory :: CategoryName
ucCategory = FilePath -> CategoryName
CategoryName FilePath
"UnresolvedCategory"
}
],
cofFiles :: [FilePath]
cofFiles = [
FilePath
"/home/project/special/object1.o",
FilePath
"/home/project/special/object1.o"
]
}
]
}
hugeModuleConfig :: ModuleConfig
hugeModuleConfig :: ModuleConfig
hugeModuleConfig = ModuleConfig {
mcRoot :: FilePath
mcRoot = FilePath
"/home/projects",
mcPath :: FilePath
mcPath = FilePath
"special",
mcExtra :: [FilePath]
mcExtra = [
FilePath
"extra1",
FilePath
"extra2"
],
mcExprMap :: [(MacroName, Expression SourceContext)]
mcExprMap = [],
mcPublicDeps :: [FilePath]
mcPublicDeps = [
FilePath
"/home/project/public-dep1",
FilePath
"/home/project/public-dep2"
],
mcPrivateDeps :: [FilePath]
mcPrivateDeps = [
FilePath
"/home/project/private-dep1",
FilePath
"/home/project/private-dep2"
],
mcExtraFiles :: [ExtraSource]
mcExtraFiles = [
CategorySource {
csSource :: FilePath
csSource = FilePath
"extra1.cpp",
csCategories :: [CategoryName]
csCategories = [
FilePath -> CategoryName
CategoryName FilePath
"Category1",
FilePath -> CategoryName
CategoryName FilePath
"Category2"
],
csRequires :: [CategoryName]
csRequires = [
FilePath -> CategoryName
CategoryName FilePath
"DepCategory1",
FilePath -> CategoryName
CategoryName FilePath
"DepCategory2"
]
},
OtherSource {
osSource :: FilePath
osSource = FilePath
"extra2.cpp"
}
],
mcCategories :: [(CategoryName, CategorySpec SourceContext)]
mcCategories = [
(FilePath -> CategoryName
CategoryName FilePath
"Category1",CategorySpec {
csContext :: [SourceContext]
csContext = [],
csRefines :: [ValueRefine SourceContext]
csRefines = [
[SourceContext] -> TypeInstance -> ValueRefine SourceContext
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] (CategoryName -> InstanceParams -> TypeInstance
TypeInstance (FilePath -> CategoryName
CategoryName FilePath
"Base1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])),
[SourceContext] -> TypeInstance -> ValueRefine SourceContext
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] (CategoryName -> InstanceParams -> TypeInstance
TypeInstance (FilePath -> CategoryName
CategoryName FilePath
"Base2") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []))
],
csDefines :: [ValueDefine SourceContext]
csDefines = [
[SourceContext] -> DefinesInstance -> ValueDefine SourceContext
forall c. [c] -> DefinesInstance -> ValueDefine c
ValueDefine [] (CategoryName -> InstanceParams -> DefinesInstance
DefinesInstance (FilePath -> CategoryName
CategoryName FilePath
"Base3") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])),
[SourceContext] -> DefinesInstance -> ValueDefine SourceContext
forall c. [c] -> DefinesInstance -> ValueDefine c
ValueDefine [] (CategoryName -> InstanceParams -> DefinesInstance
DefinesInstance (FilePath -> CategoryName
CategoryName FilePath
"Base4") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []))
]
}),
(FilePath -> CategoryName
CategoryName FilePath
"Category2",CategorySpec {
csContext :: [SourceContext]
csContext = [],
csRefines :: [ValueRefine SourceContext]
csRefines = [
[SourceContext] -> TypeInstance -> ValueRefine SourceContext
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] (CategoryName -> InstanceParams -> TypeInstance
TypeInstance (FilePath -> CategoryName
CategoryName FilePath
"Base1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])),
[SourceContext] -> TypeInstance -> ValueRefine SourceContext
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] (CategoryName -> InstanceParams -> TypeInstance
TypeInstance (FilePath -> CategoryName
CategoryName FilePath
"Base2") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []))
],
csDefines :: [ValueDefine SourceContext]
csDefines = [
[SourceContext] -> DefinesInstance -> ValueDefine SourceContext
forall c. [c] -> DefinesInstance -> ValueDefine c
ValueDefine [] (CategoryName -> InstanceParams -> DefinesInstance
DefinesInstance (FilePath -> CategoryName
CategoryName FilePath
"Base3") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])),
[SourceContext] -> DefinesInstance -> ValueDefine SourceContext
forall c. [c] -> DefinesInstance -> ValueDefine c
ValueDefine [] (CategoryName -> InstanceParams -> DefinesInstance
DefinesInstance (FilePath -> CategoryName
CategoryName FilePath
"Base4") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []))
]
})
],
mcExtraPaths :: [FilePath]
mcExtraPaths = [
FilePath
"extra1",
FilePath
"extra2"
],
mcMode :: CompileMode
mcMode = CompileIncremental {
ciLinkFlags :: [FilePath]
ciLinkFlags = [
FilePath
"-lm",
FilePath
"-ldl"
]
}
}
tests :: [IO (TrackedErrors ())]
tests :: [IO (TrackedErrors ())]
tests = [
CompileMetadata -> IO (TrackedErrors ())
forall a.
(Eq a, Show a, ConfigFormat a) =>
a -> IO (TrackedErrors ())
checkWriteThenRead CompileMetadata
hugeCompileMetadata,
FilePath -> CompileMetadata -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad hash" (CompileMetadata -> IO (TrackedErrors ()))
-> CompileMetadata -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileMetadata {
cmVersionHash :: VersionHash
cmVersionHash = FilePath -> VersionHash
VersionHash FilePath
"bad hash",
cmRoot :: FilePath
cmRoot = FilePath
"/home/project",
cmPath :: FilePath
cmPath = FilePath
"/home/project/special",
cmExtra :: [FilePath]
cmExtra = [],
cmPublicNamespace :: Namespace
cmPublicNamespace = Namespace
NoNamespace,
cmPrivateNamespace :: Namespace
cmPrivateNamespace = Namespace
NoNamespace,
cmPublicDeps :: [FilePath]
cmPublicDeps = [],
cmPrivateDeps :: [FilePath]
cmPrivateDeps = [],
cmPublicCategories :: [CategoryName]
cmPublicCategories = [],
cmPrivateCategories :: [CategoryName]
cmPrivateCategories = [],
cmPublicSubdirs :: [FilePath]
cmPublicSubdirs = [],
cmPrivateSubdirs :: [FilePath]
cmPrivateSubdirs = [],
cmPublicFiles :: [FilePath]
cmPublicFiles = [],
cmPrivateFiles :: [FilePath]
cmPrivateFiles = [],
cmTestFiles :: [FilePath]
cmTestFiles = [],
cmHxxFiles :: [FilePath]
cmHxxFiles = [],
cmCxxFiles :: [FilePath]
cmCxxFiles = [],
cmBinaries :: [FilePath]
cmBinaries = [],
cmLibraries :: [FilePath]
cmLibraries = [],
cmLinkFlags :: [FilePath]
cmLinkFlags = [],
cmObjectFiles :: [ObjectFile]
cmObjectFiles = []
},
FilePath -> CompileMetadata -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad namespace" (CompileMetadata -> IO (TrackedErrors ()))
-> CompileMetadata -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileMetadata {
cmVersionHash :: VersionHash
cmVersionHash = FilePath -> VersionHash
VersionHash FilePath
"0123456789ABCDEFabcdef",
cmRoot :: FilePath
cmRoot = FilePath
"/home/project",
cmPath :: FilePath
cmPath = FilePath
"/home/project/special",
cmExtra :: [FilePath]
cmExtra = [],
cmPublicNamespace :: Namespace
cmPublicNamespace = FilePath -> Namespace
StaticNamespace FilePath
"bad namespace",
cmPrivateNamespace :: Namespace
cmPrivateNamespace = Namespace
NoNamespace,
cmPublicDeps :: [FilePath]
cmPublicDeps = [],
cmPrivateDeps :: [FilePath]
cmPrivateDeps = [],
cmPublicCategories :: [CategoryName]
cmPublicCategories = [],
cmPrivateCategories :: [CategoryName]
cmPrivateCategories = [],
cmPublicSubdirs :: [FilePath]
cmPublicSubdirs = [],
cmPrivateSubdirs :: [FilePath]
cmPrivateSubdirs = [],
cmPublicFiles :: [FilePath]
cmPublicFiles = [],
cmPrivateFiles :: [FilePath]
cmPrivateFiles = [],
cmTestFiles :: [FilePath]
cmTestFiles = [],
cmHxxFiles :: [FilePath]
cmHxxFiles = [],
cmCxxFiles :: [FilePath]
cmCxxFiles = [],
cmBinaries :: [FilePath]
cmBinaries = [],
cmLibraries :: [FilePath]
cmLibraries = [],
cmLinkFlags :: [FilePath]
cmLinkFlags = [],
cmObjectFiles :: [ObjectFile]
cmObjectFiles = []
},
FilePath -> CompileMetadata -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad namespace" (CompileMetadata -> IO (TrackedErrors ()))
-> CompileMetadata -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileMetadata {
cmVersionHash :: VersionHash
cmVersionHash = FilePath -> VersionHash
VersionHash FilePath
"0123456789ABCDEFabcdef",
cmRoot :: FilePath
cmRoot = FilePath
"/home/project",
cmPath :: FilePath
cmPath = FilePath
"/home/project/special",
cmExtra :: [FilePath]
cmExtra = [],
cmPublicNamespace :: Namespace
cmPublicNamespace = Namespace
NoNamespace,
cmPrivateNamespace :: Namespace
cmPrivateNamespace = FilePath -> Namespace
StaticNamespace FilePath
"bad namespace",
cmPublicDeps :: [FilePath]
cmPublicDeps = [],
cmPrivateDeps :: [FilePath]
cmPrivateDeps = [],
cmPublicCategories :: [CategoryName]
cmPublicCategories = [],
cmPrivateCategories :: [CategoryName]
cmPrivateCategories = [],
cmPublicSubdirs :: [FilePath]
cmPublicSubdirs = [],
cmPrivateSubdirs :: [FilePath]
cmPrivateSubdirs = [],
cmPublicFiles :: [FilePath]
cmPublicFiles = [],
cmPrivateFiles :: [FilePath]
cmPrivateFiles = [],
cmTestFiles :: [FilePath]
cmTestFiles = [],
cmHxxFiles :: [FilePath]
cmHxxFiles = [],
cmCxxFiles :: [FilePath]
cmCxxFiles = [],
cmBinaries :: [FilePath]
cmBinaries = [],
cmLibraries :: [FilePath]
cmLibraries = [],
cmLinkFlags :: [FilePath]
cmLinkFlags = [],
cmObjectFiles :: [ObjectFile]
cmObjectFiles = []
},
FilePath -> CompileMetadata -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad category" (CompileMetadata -> IO (TrackedErrors ()))
-> CompileMetadata -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileMetadata {
cmVersionHash :: VersionHash
cmVersionHash = FilePath -> VersionHash
VersionHash FilePath
"0123456789ABCDEFabcdef",
cmRoot :: FilePath
cmRoot = FilePath
"/home/project",
cmPath :: FilePath
cmPath = FilePath
"/home/project/special",
cmExtra :: [FilePath]
cmExtra = [],
cmPublicNamespace :: Namespace
cmPublicNamespace = Namespace
NoNamespace,
cmPrivateNamespace :: Namespace
cmPrivateNamespace = Namespace
NoNamespace,
cmPublicDeps :: [FilePath]
cmPublicDeps = [],
cmPrivateDeps :: [FilePath]
cmPrivateDeps = [],
cmPublicCategories :: [CategoryName]
cmPublicCategories = [
FilePath -> CategoryName
CategoryName FilePath
"bad category"
],
cmPrivateCategories :: [CategoryName]
cmPrivateCategories = [],
cmPublicSubdirs :: [FilePath]
cmPublicSubdirs = [],
cmPrivateSubdirs :: [FilePath]
cmPrivateSubdirs = [],
cmPublicFiles :: [FilePath]
cmPublicFiles = [],
cmPrivateFiles :: [FilePath]
cmPrivateFiles = [],
cmTestFiles :: [FilePath]
cmTestFiles = [],
cmHxxFiles :: [FilePath]
cmHxxFiles = [],
cmCxxFiles :: [FilePath]
cmCxxFiles = [],
cmBinaries :: [FilePath]
cmBinaries = [],
cmLibraries :: [FilePath]
cmLibraries = [],
cmLinkFlags :: [FilePath]
cmLinkFlags = [],
cmObjectFiles :: [ObjectFile]
cmObjectFiles = []
},
FilePath -> CompileMetadata -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad category" (CompileMetadata -> IO (TrackedErrors ()))
-> CompileMetadata -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileMetadata {
cmVersionHash :: VersionHash
cmVersionHash = FilePath -> VersionHash
VersionHash FilePath
"0123456789ABCDEFabcdef",
cmRoot :: FilePath
cmRoot = FilePath
"/home/project",
cmPath :: FilePath
cmPath = FilePath
"/home/project/special",
cmExtra :: [FilePath]
cmExtra = [],
cmPublicNamespace :: Namespace
cmPublicNamespace = Namespace
NoNamespace,
cmPrivateNamespace :: Namespace
cmPrivateNamespace = Namespace
NoNamespace,
cmPublicDeps :: [FilePath]
cmPublicDeps = [],
cmPrivateDeps :: [FilePath]
cmPrivateDeps = [],
cmPublicCategories :: [CategoryName]
cmPublicCategories = [],
cmPrivateCategories :: [CategoryName]
cmPrivateCategories = [
FilePath -> CategoryName
CategoryName FilePath
"bad category"
],
cmPublicSubdirs :: [FilePath]
cmPublicSubdirs = [],
cmPrivateSubdirs :: [FilePath]
cmPrivateSubdirs = [],
cmPublicFiles :: [FilePath]
cmPublicFiles = [],
cmPrivateFiles :: [FilePath]
cmPrivateFiles = [],
cmTestFiles :: [FilePath]
cmTestFiles = [],
cmHxxFiles :: [FilePath]
cmHxxFiles = [],
cmCxxFiles :: [FilePath]
cmCxxFiles = [],
cmBinaries :: [FilePath]
cmBinaries = [],
cmLibraries :: [FilePath]
cmLibraries = [],
cmLinkFlags :: [FilePath]
cmLinkFlags = [],
cmObjectFiles :: [ObjectFile]
cmObjectFiles = []
},
ModuleConfig -> IO (TrackedErrors ())
forall a.
(Eq a, Show a, ConfigFormat a) =>
a -> IO (TrackedErrors ())
checkWriteThenRead ModuleConfig
hugeModuleConfig,
FilePath -> ModuleConfig -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"empty.+map" (ModuleConfig -> IO (TrackedErrors ()))
-> ModuleConfig -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ ModuleConfig {
mcRoot :: FilePath
mcRoot = FilePath
"/home/projects",
mcPath :: FilePath
mcPath = FilePath
"special",
mcExtra :: [FilePath]
mcExtra = [],
mcExprMap :: [(MacroName, Expression SourceContext)]
mcExprMap = [(FilePath -> MacroName
MacroName FilePath
"MACRO",ValueLiteral SourceContext -> Expression SourceContext
forall c. ValueLiteral c -> Expression c
Literal ([SourceContext] -> FilePath -> ValueLiteral SourceContext
forall c. [c] -> FilePath -> ValueLiteral c
StringLiteral [] FilePath
"something"))],
mcPublicDeps :: [FilePath]
mcPublicDeps = [],
mcPrivateDeps :: [FilePath]
mcPrivateDeps = [],
mcExtraFiles :: [ExtraSource]
mcExtraFiles = [],
mcCategories :: [(CategoryName, CategorySpec SourceContext)]
mcCategories = [],
mcExtraPaths :: [FilePath]
mcExtraPaths = [],
mcMode :: CompileMode
mcMode = CompileIncremental {
ciLinkFlags :: [FilePath]
ciLinkFlags = []
}
},
FilePath -> ExtraSource -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad category" (ExtraSource -> IO (TrackedErrors ()))
-> ExtraSource -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CategorySource {
csSource :: FilePath
csSource = FilePath
"extra1.cpp",
csCategories :: [CategoryName]
csCategories = [
FilePath -> CategoryName
CategoryName FilePath
"bad category"
],
csRequires :: [CategoryName]
csRequires = []
},
FilePath -> ExtraSource -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad category" (ExtraSource -> IO (TrackedErrors ()))
-> ExtraSource -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CategorySource {
csSource :: FilePath
csSource = FilePath
"extra1.cpp",
csCategories :: [CategoryName]
csCategories = [],
csRequires :: [CategoryName]
csRequires = [
FilePath -> CategoryName
CategoryName FilePath
"bad category"
]
},
FilePath -> CategoryIdentifier -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad category" (CategoryIdentifier -> IO (TrackedErrors ()))
-> CategoryIdentifier -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CategoryIdentifier {
ciPath :: FilePath
ciPath = FilePath
"/home/project/special",
ciCategory :: CategoryName
ciCategory = FilePath -> CategoryName
CategoryName FilePath
"bad category",
ciNamespace :: Namespace
ciNamespace = Namespace
NoNamespace
},
FilePath -> CategoryIdentifier -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad namespace" (CategoryIdentifier -> IO (TrackedErrors ()))
-> CategoryIdentifier -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CategoryIdentifier {
ciPath :: FilePath
ciPath = FilePath
"/home/project/special",
ciCategory :: CategoryName
ciCategory = FilePath -> CategoryName
CategoryName FilePath
"SpecialCategory",
ciNamespace :: Namespace
ciNamespace = FilePath -> Namespace
StaticNamespace FilePath
"bad namespace"
},
FilePath -> CategoryIdentifier -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad category" (CategoryIdentifier -> IO (TrackedErrors ()))
-> CategoryIdentifier -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ UnresolvedCategory {
ucCategory :: CategoryName
ucCategory = FilePath -> CategoryName
CategoryName FilePath
"bad category"
},
CompileMode -> IO (TrackedErrors ())
forall a.
(Eq a, Show a, ConfigFormat a) =>
a -> IO (TrackedErrors ())
checkWriteThenRead (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileBinary {
cbCategory :: CategoryName
cbCategory = FilePath -> CategoryName
CategoryName FilePath
"SpecialCategory",
cbFunction :: FunctionName
cbFunction = FilePath -> FunctionName
FunctionName FilePath
"specialFunction",
cbLinker :: LinkerMode
cbLinker = LinkerMode
LinkStatic,
cbOutputName :: FilePath
cbOutputName = FilePath
"binary",
cbLinkFlags :: [FilePath]
cbLinkFlags = []
},
CompileMode -> IO (TrackedErrors ())
forall a.
(Eq a, Show a, ConfigFormat a) =>
a -> IO (TrackedErrors ())
checkWriteThenRead (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileBinary {
cbCategory :: CategoryName
cbCategory = FilePath -> CategoryName
CategoryName FilePath
"SpecialCategory",
cbFunction :: FunctionName
cbFunction = FilePath -> FunctionName
FunctionName FilePath
"specialFunction",
cbLinker :: LinkerMode
cbLinker = LinkerMode
LinkDynamic,
cbOutputName :: FilePath
cbOutputName = FilePath
"binary",
cbLinkFlags :: [FilePath]
cbLinkFlags = []
},
FilePath -> CompileMode -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad category" (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileBinary {
cbCategory :: CategoryName
cbCategory = FilePath -> CategoryName
CategoryName FilePath
"bad category",
cbFunction :: FunctionName
cbFunction = FilePath -> FunctionName
FunctionName FilePath
"specialFunction",
cbLinker :: LinkerMode
cbLinker = LinkerMode
LinkDynamic,
cbOutputName :: FilePath
cbOutputName = FilePath
"binary",
cbLinkFlags :: [FilePath]
cbLinkFlags = []
},
FilePath -> CompileMode -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"bad function" (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileBinary {
cbCategory :: CategoryName
cbCategory = FilePath -> CategoryName
CategoryName FilePath
"SpecialCategory",
cbFunction :: FunctionName
cbFunction = FilePath -> FunctionName
FunctionName FilePath
"bad function",
cbLinker :: LinkerMode
cbLinker = LinkerMode
LinkDynamic,
cbOutputName :: FilePath
cbOutputName = FilePath
"binary",
cbLinkFlags :: [FilePath]
cbLinkFlags = []
},
FilePath -> CompileMode -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"compile mode" (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileFast {
cfCategory :: CategoryName
cfCategory = FilePath -> CategoryName
CategoryName FilePath
"SpecialCategory",
cfFunction :: FunctionName
cfFunction = FilePath -> FunctionName
FunctionName FilePath
"specialFunction",
cfSource :: FilePath
cfSource = FilePath
"source.0rx"
},
CompileMode -> IO (TrackedErrors ())
forall a.
(Eq a, Show a, ConfigFormat a) =>
a -> IO (TrackedErrors ())
checkWriteThenRead (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileIncremental {
ciLinkFlags :: [FilePath]
ciLinkFlags = [
FilePath
"-lm",
FilePath
"-ldl"
]
},
FilePath -> CompileMode -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"compile mode" (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ ExecuteTests { etInclude :: [FilePath]
etInclude = [], etCallLog :: Maybe FilePath
etCallLog = Maybe FilePath
forall a. Maybe a
Nothing },
FilePath -> CompileMode -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"compile mode" (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileMode
CompileRecompile,
FilePath -> CompileMode -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"compile mode" (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileMode
CompileRecompileRecursive,
FilePath -> CompileMode -> IO (TrackedErrors ())
forall a. ConfigFormat a => FilePath -> a -> IO (TrackedErrors ())
checkWriteFail FilePath
"compile mode" (CompileMode -> IO (TrackedErrors ()))
-> CompileMode -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ CompileMode
CreateTemplates,
FilePath -> (ModuleConfig -> Bool) -> IO (TrackedErrors ())
forall a.
(Show a, ConfigFormat a) =>
FilePath -> (a -> Bool) -> IO (TrackedErrors ())
checkParsesAs (FilePath
"testfiles" FilePath -> FilePath -> FilePath
</> FilePath
"macro-config.txt")
(\ModuleConfig
m -> case ModuleConfig -> [(MacroName, Expression SourceContext)]
mcExprMap ModuleConfig
m of
[(MacroName FilePath
"MY_MACRO",
Expression [SourceContext]
_ (BuiltinCall [SourceContext]
_
(FunctionCall [SourceContext]
_ FunctionName
BuiltinRequire (Positional [])
(Positional [(Maybe (CallArgLabel SourceContext)
Nothing,Expression [SourceContext]
_ (UnambiguousLiteral (EmptyLiteral [SourceContext]
_)) [])]))) []),
(MacroName FilePath
"MY_OTHER_MACRO",
Expression [SourceContext]
_
(TypeCall [SourceContext]
_ TypeInstanceOrParam
_
(FunctionCall [SourceContext]
_ (FunctionName FilePath
"execute") (Positional [])
(Positional [(Maybe (CallArgLabel SourceContext)
Nothing,Expression [SourceContext]
_ (UnambiguousLiteral (StringLiteral [SourceContext]
_ FilePath
"this is a string\n")) [])]))) [])
] -> Bool
True
[(MacroName, Expression SourceContext)]
_ -> Bool
False),
FilePath -> (ModuleConfig -> Bool) -> IO (TrackedErrors ())
forall a.
(Show a, ConfigFormat a) =>
FilePath -> (a -> Bool) -> IO (TrackedErrors ())
checkParsesAs (FilePath
"testfiles" FilePath -> FilePath -> FilePath
</> FilePath
"module-config.txt") (ModuleConfig -> ModuleConfig -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleConfig
hugeModuleConfig),
FilePath -> (CompileMetadata -> Bool) -> IO (TrackedErrors ())
forall a.
(Show a, ConfigFormat a) =>
FilePath -> (a -> Bool) -> IO (TrackedErrors ())
checkParsesAs (FilePath
"testfiles" FilePath -> FilePath -> FilePath
</> FilePath
"module-cache.txt") (CompileMetadata -> CompileMetadata -> Bool
forall a. Eq a => a -> a -> Bool
== CompileMetadata
hugeCompileMetadata)
]
checkParsesAs :: (Show a, ConfigFormat a) => String -> (a -> Bool) -> IO (TrackedErrors ())
checkParsesAs :: forall a.
(Show a, ConfigFormat a) =>
FilePath -> (a -> Bool) -> IO (TrackedErrors ())
checkParsesAs FilePath
f a -> Bool
m = do
FilePath
contents <- FilePath -> IO FilePath
loadFile FilePath
f
let parsed :: TrackedErrorsT Identity a
parsed = FilePath -> FilePath -> TrackedErrorsT Identity a
forall a (m :: * -> *).
(ConfigFormat a, ErrorContextM m) =>
FilePath -> FilePath -> m a
autoReadConfig FilePath
f FilePath
contents
TrackedErrors () -> IO (TrackedErrors ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackedErrors () -> IO (TrackedErrors ()))
-> TrackedErrors () -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ TrackedErrorsT Identity a -> FilePath -> TrackedErrors ()
forall {m :: * -> *}. ErrorContextM m => m a -> FilePath -> m ()
check TrackedErrorsT Identity a
parsed FilePath
contents
where
check :: m a -> FilePath -> m ()
check m a
x FilePath
contents = do
a
x' <- m a
x m a -> FilePath -> m a
forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<!! FilePath
"While parsing " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
f
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ a -> Bool
m a
x') (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
FilePath -> m ()
forall a. FilePath -> m a
forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM (FilePath -> m ()) -> FilePath -> m ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Failed to match after write/read\n" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
"Unparsed:\n" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
contents FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
FilePath
"Parsed:\n" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ a -> FilePath
forall a. Show a => a -> FilePath
show a
x' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"